aic7xxx.seq revision 9810
1##+M#########################################################################
2# Adaptec 274x/284x/294x device driver for Linux and FreeBSD.
3#
4# Copyright (c) 1994 John Aycock
5#   The University of Calgary Department of Computer Science.
6#   All rights reserved.
7#
8# Modifications/enhancements:
9#   Copyright (c) 1994, 1995 Justin Gibbs. All rights reserved.
10#
11# Redistribution and use in source and binary forms, with or without
12# modification, are permitted provided that the following conditions
13# are met:
14# 1. Redistributions of source code must retain the above copyright
15#    notice, this list of conditions, and the following disclaimer.
16# 2. Redistributions in binary form must reproduce the above copyright
17#    notice, this list of conditions and the following disclaimer in the
18#    documentation and/or other materials provided with the distribution.
19# 3. All advertising materials mentioning features or use of this software
20#    must display the following acknowledgement:
21#      This product includes software developed by the University of Calgary
22#      Department of Computer Science and its contributors.
23# 4. Neither the name of the University nor the names of its contributors
24#    may be used to endorse or promote products derived from this software
25#    without specific prior written permission.
26#
27# THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
28# ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
29# IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
30# ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
31# FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
32# DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
33# OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
34# HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
35# LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
36# OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
37# SUCH DAMAGE.
38# 
39# FreeBSD, Twin, Wide, 2 command per target support, tagged queuing and other 
40# optimizations provided by Justin T. Gibbs (gibbs@FreeBSD.org)
41#
42##-M#########################################################################
43
44VERSION AIC7XXX_SEQ_VER "$Id: aic7xxx.seq,v 1.17 1995/07/04 20:58:57 gibbs Exp $"
45
46SCBMASK		= 0x1f
47
48SCSISEQ		= 0x00
49ENRSELI		= 0x10
50SXFRCTL0	= 0x01
51SXFRCTL1	= 0x02
52SCSISIGI	= 0x03
53SCSISIGO	= 0x03
54SCSIRATE	= 0x04
55SCSIID		= 0x05
56SCSIDATL	= 0x06
57STCNT		= 0x08
58STCNT+0		= 0x08
59STCNT+1		= 0x09
60STCNT+2		= 0x0a
61CLRSINT0	= 0x0b
62SSTAT0		= 0x0b
63SELDO		= 0x40
64SELDI		= 0x20
65CLRSINT1	= 0x0c
66SSTAT1		= 0x0c
67SIMODE1		= 0x11
68SCSIBUSL	= 0x12
69SHADDR		= 0x14
70SELID		= 0x19
71SBLKCTL		= 0x1f
72SEQCTL		= 0x60
73A		= 0x64				# == ACCUM
74SINDEX		= 0x65
75DINDEX		= 0x66
76ALLZEROS	= 0x6a
77NONE		= 0x6a
78SINDIR		= 0x6c
79DINDIR		= 0x6d
80FUNCTION1	= 0x6e
81HADDR		= 0x88
82HADDR+1		= 0x89
83HADDR+2		= 0x8a
84HADDR+3		= 0x8b
85HCNT		= 0x8c
86HCNT+0		= 0x8c
87HCNT+1		= 0x8d
88HCNT+2		= 0x8e
89SCBPTR		= 0x90
90INTSTAT		= 0x91
91DFCNTRL		= 0x93
92DFSTATUS	= 0x94
93DFDAT		= 0x99
94QINFIFO		= 0x9b
95QINCNT		= 0x9c
96QOUTFIFO	= 0x9d
97
98SCSICONF_A	= 0x5a
99SCSICONF_B	= 0x5b
100
101#  The two reserved bytes at SCBARRAY+1[23] are expected to be set to
102#  zero, and the reserved bit in SCBARRAY+0 is used as an internal flag
103#  to indicate whether or not to reload scatter-gather parameters after
104#  a disconnect.  We also use bits 6 & 7 to indicate whether or not to
105#  initiate SDTR or WDTR repectively when starting this command.
106#
107SCBARRAY+0	= 0xa0
108
109DISCONNECTED	= 0x04
110NEEDDMA		= 0x08
111SG_LOAD		= 0x10
112TAG_ENB		= 0x20
113NEEDSDTR	= 0x40
114NEEDWDTR	= 0x80
115
116SCBARRAY+1	= 0xa1
117SCBARRAY+2	= 0xa2
118SCBARRAY+3	= 0xa3
119SCBARRAY+4	= 0xa4
120SCBARRAY+5	= 0xa5
121SCBARRAY+6	= 0xa6
122SCBARRAY+7	= 0xa7
123SCBARRAY+8	= 0xa8
124SCBARRAY+9	= 0xa9
125SCBARRAY+10	= 0xaa
126SCBARRAY+11	= 0xab
127SCBARRAY+12	= 0xac
128SCBARRAY+13	= 0xad
129SCBARRAY+14	= 0xae
130SCBARRAY+15	= 0xaf
131SCBARRAY+16	= 0xb0
132SCBARRAY+17	= 0xb1
133SCBARRAY+18	= 0xb2
134SCBARRAY+19	= 0xb3
135SCBARRAY+20	= 0xb4
136SCBARRAY+21	= 0xb5
137SCBARRAY+22	= 0xb6
138SCBARRAY+23	= 0xb7
139SCBARRAY+24	= 0xb8
140SCBARRAY+25	= 0xb9
141SCBARRAY+26	= 0xba
142SCBARRAY+27	= 0xbb
143SCBARRAY+28	= 0xbc
144SCBARRAY+29	= 0xbd
145SCBARRAY+30	= 0xbe
146
147BAD_PHASE	= 0x01				# unknown scsi bus phase
148CMDCMPLT	= 0x02				# Command Complete
149SEND_REJECT	= 0x11				# sending a message reject
150NO_IDENT	= 0x21				# no IDENTIFY after reconnect
151NO_MATCH	= 0x31				# no cmd match for reconnect
152MSG_SDTR	= 0x41				# SDTR message recieved
153MSG_WDTR	= 0x51				# WDTR message recieved
154MSG_REJECT	= 0x61				# Reject message recieved
155BAD_STATUS	= 0x71				# Bad status from target
156RESIDUAL	= 0x81				# Residual byte count != 0
157ABORT_TAG	= 0x91				# Sent an ABORT_TAG message
158AWAITING_MSG	= 0xa1				# Kernel requested to specify
159						# a message to this target
160						# (command was null), so tell
161						# it that it can fill the
162						# message buffer.
163IMMEDDONE	= 0xb1
164
165
166#  The host adapter card (at least the BIOS) uses 20-2f for SCSI
167#  device information, 32-33 and 5a-5f as well. As it turns out, the
168#  BIOS trashes 20-2f, writing the synchronous negotiation results
169#  on top of the BIOS values, so we re-use those for our per-target
170#  scratchspace (actually a value that can be copied directly into
171#  SCSIRATE).  The kernel driver will enable synchronous negotiation
172#  for all targets that have a value other than 0 in the lower four
173#  bits of the target scratch space.  This should work irregardless of
174#  whether the bios has been installed. NEEDWDTR and NEEDSDTR are the top
175#  two bits of the SCB control byte.  The kernel driver will set these
176#  when a WDTR or SDTR message should be sent to the target the SCB's 
177#  command references.
178#
179#  REJBYTE contains the first byte of a MESSAGE IN message, so the driver 
180#  can report an intelligible error if a message is rejected.
181#
182#  FLAGS's high bit is true if we are currently handling a reselect;
183#  its next-highest bit is true ONLY IF we've seen an IDENTIFY message
184#  from the reselecting target.  If we haven't had IDENTIFY, then we have
185#  no idea what the lun is, and we can't select the right SCB register
186#  bank, so force a kernel panic if the target attempts a data in/out or
187#  command phase instead of corrupting something.  FLAGS also contains
188#  configuration bits so that we can optimize for TWIN and WIDE controllers
189#  as well as the MAX_OFFSET bit which we set when we want to negotiate for
190#  maximum sync offset irregardless of what the per target scratch space says.
191#
192#  Note that SG_NEXT occupies four bytes.
193#
194SYNCNEG		= 0x20
195
196REJBYTE		= 0x31
197DISC_DSB_A	= 0x32
198DISC_DSB_B	= 0x33
199
200MSG_LEN		= 0x34
201MSG_START+0	= 0x35
202MSG_START+1	= 0x36
203MSG_START+2	= 0x37
204MSG_START+3	= 0x38
205MSG_START+4	= 0x39
206MSG_START+5	= 0x3a
207-MSG_START+0	= 0xcb				# 2's complement of MSG_START+0
208
209ARG_1		= 0x4a				# sdtr conversion args & return
210BUS_16_BIT	= 0x01
211RETURN_1	= 0x4a
212
213SIGSTATE	= 0x4b				# value written to SCSISIGO
214
215# Linux users should use 0xc (12) for SG_SIZEOF
216SG_SIZEOF	= 0x8 				# sizeof(struct ahc_dma)
217#SG_SIZEOF	= 0xc 				# sizeof(struct scatterlist)
218SCB_SIZEOF	= 0x13				# sizeof SCB to DMA (19 bytes)
219
220SG_NOLOAD	= 0x4c				# load SG pointer/length?
221SG_COUNT	= 0x4d				# working value of SG count
222SG_NEXT		= 0x4e				# working value of SG pointer
223SG_NEXT+0	= 0x4e
224SG_NEXT+1	= 0x4f
225SG_NEXT+2	= 0x50
226SG_NEXT+3	= 0x51
227
228SCBCOUNT	= 0x52				# the actual number of SCBs
229FLAGS		= 0x53				# Device configuration flags
230TWIN_BUS	= 0x01
231WIDE_BUS	= 0x02
232MAX_OFFSET	= 0x08
233ACTIVE_MSG	= 0x20
234IDENTIFY_SEEN	= 0x40
235RESELECTED	= 0x80
236
237MAX_OFFSET_8BIT	= 0x0f
238MAX_OFFSET_WIDE	= 0x08
239
240ACTIVE_A	= 0x54
241ACTIVE_B	= 0x55
242SAVED_TCL	= 0x56				# Temporary storage for the 
243						# target/channel/lun of a
244						# reconnecting target
245
246# After starting the selection hardware, we return to the "poll_for_work"
247# loop so that we can check for reconnecting targets as well as for our
248# selection to complete just in case the reselection wins bus arbitration.
249# The problem with this is that we must keep track of the SCB that we've
250# already pulled from the QINFIFO and started the selection on just in case
251# the reselection wins so that we can retry the selection at a later time.
252# This problem cannot be resolved by holding a single entry in scratch
253# ram since a reconnecting target can request sense and this will create
254# yet another SCB waiting for selection.  The solution used here is to 
255# use byte 31 of the SCB as a psuedo-next pointer and to thread a list
256# of SCBs that are awaiting selection.  Since 0-0xfe are valid SCB offsets, 
257# SCB_LIST_NULL is 0xff which is out of range.  The kernel driver must
258# add an entry to this list everytime a request sense occurs.  The sequencer
259# will automatically consume the entries.
260
261WAITING_SCBH	= 0x57				# head of list of SCBs awaiting
262						# selection
263WAITING_SCBT	= 0x58				# tail of list of SCBs awaiting
264						# selection
265SCB_LIST_NULL	= 0xff
266
267
268#  Poll QINCNT for work - the lower bits contain
269#  the number of entries in the Queue In FIFO.
270#
271start:
272	cmp	WAITING_SCBH,SCB_LIST_NULL jne start_waiting
273poll_for_work:
274	test	FLAGS,TWIN_BUS	jz start2	# Are we a twin channel device?
275# For fairness, we check the other bus first, since we just finished a 
276# transaction on the current channel.
277	xor	SBLKCTL,0x08			# Toggle to the other bus
278	test	SSTAT0,SELDI	jnz reselect
279	test	SSTAT0,SELDO	jnz select
280	xor	SBLKCTL,0x08			# Toggle to the original bus
281start2:
282	test	SSTAT0,SELDI	jnz reselect
283	test	SSTAT0,SELDO	jnz select
284	cmp	WAITING_SCBH,SCB_LIST_NULL jne start_waiting
285	test	QINCNT,SCBMASK	jz poll_for_work
286
287# We have at least one queued SCB now and we don't have any 
288# SCBs in the list of SCBs awaiting selection.  Set the SCB
289# pointer from the FIFO so we see the right bank of SCB 
290# registers, then set SCSI options and set the initiator and
291# target SCSI IDs.
292#
293	mov	SCBPTR,QINFIFO
294
295# If the control byte of this SCB has the NEEDDMA flag set, we have
296# yet to DMA it from host memory
297
298test    SCBARRAY+0,NEEDDMA      jz test_busy    
299	clr	HCNT+2
300	clr	HCNT+1
301	mvi	HCNT+0,SCB_SIZEOF
302
303	mvi	DINDEX,HADDR      
304	mvi	SCBARRAY+26     call bcopy_4
305        
306	mvi	DFCNTRL,0xd                     # HDMAEN|DIRECTION|FIFORESET
307
308#  Wait for DMA from host memory to data FIFO to complete, then disable
309#  DMA and wait for it to acknowledge that it's off.
310#
311	call	dma_finish
312
313# Copy the SCB from the FIFO to  the SCBARRAY
314
315	mvi	DINDEX, SCBARRAY+0
316	call	bcopy_3_dfdat 
317	call	bcopy_4_dfdat
318	call	bcopy_4_dfdat
319	call	bcopy_4_dfdat   
320	call	bcopy_4_dfdat
321
322# See if there is not already an active SCB for this target.  This code
323# locks out on a per target basis instead of target/lun.  Although this
324# is not ideal for devices that have multiple luns active at the same
325# time, it is faster than looping through all SCB's looking for active
326# commands.  It may be benificial to make findscb a more general procedure
327# to see if the added cost of the search is negligible.  This code also 
328# assumes that the kernel driver will clear the active flags on board 
329# initialization, board reset, and a target's SELTO.
330
331test_busy:
332	and	FUNCTION1,0x70,SCBARRAY+1
333	mov	A,FUNCTION1
334	test	SCBARRAY+1,0x88	jz test_a	# Id < 8 && A channel
335
336	test	ACTIVE_B,A	jnz requeue
337	test	SCBARRAY+0,0x20	jnz start_scb
338	or	ACTIVE_B,A	# Mark the current target as busy
339	jmp	start_scb
340
341# Place the currently active back on the queue for later processing
342requeue:
343	mov	QINFIFO, SCBPTR
344	jmp	poll_for_work
345
346# Pull the first entry off of the waiting for selection list
347start_waiting:
348	mov	SCBPTR,WAITING_SCBH
349	jmp	start_scb
350
351test_a:
352	test	ACTIVE_A,A	jnz requeue
353	test	SCBARRAY+0,0x20	jnz start_scb
354	or	ACTIVE_A,A	# Mark the current target as busy
355
356start_scb:
357	and	SINDEX,0xf7,SBLKCTL  #Clear the channel select bit
358	and	A,0x08,SCBARRAY+1    #Get new channel bit
359	or	SINDEX,A	     
360	mov	SBLKCTL,SINDEX	# select channel
361	mov	SCBARRAY+1	call initialize_scsiid
362
363# Enable selection phase as an initiator, and do automatic ATN
364# after the selection.  We do this now so that we can overlap the
365# rest of our work to set up this target with the arbitration and
366# selection bus phases.
367#
368start_selection:
369	or	SCSISEQ,0x48			# ENSELO|ENAUTOATNO
370	mov	WAITING_SCBH, SCBPTR
371	clr	SG_NOLOAD
372	and	FLAGS,0x3f	# !RESELECTING
373
374#  As soon as we get a successful selection, the target should go
375#  into the message out phase since we have ATN asserted.  Prepare
376#  the message to send, locking out the device driver.  If the device
377#  driver hasn't beaten us with an ABORT or RESET message, then tack
378#  on an SDTR negotiation if required.
379#
380#  Messages are stored in scratch RAM starting with a flag byte (high bit
381#  set means active message), one length byte, and then the message itself.
382#
383
384	test	SCBARRAY+11,0xff jnz identify	# 0 Length Command?
385
386#  The kernel has sent us an SCB with no command attached.  This implies
387#  that the kernel wants to send a message of some sort to this target,
388#  so we interrupt the driver, allow it to fill the message buffer, and
389#  then go back into the arbitration loop
390	mvi     INTSTAT,AWAITING_MSG
391	jmp     poll_for_work
392
393identify:
394	mov	SCBARRAY+1	call disconnect	# disconnect ok?
395
396	and	SINDEX,0x7,SCBARRAY+1		# lun
397	or	SINDEX,A			# return value from disconnect
398	or	SINDEX,0x80	call mk_mesg	# IDENTIFY message
399
400	mov	A,SINDEX
401	test	SCBARRAY+0,0xe0	jz  !message	# WDTR, SDTR or TAG??
402	cmp	MSG_START+0,A	jne !message	# did driver beat us?
403
404# Tag Message if Tag enabled in SCB control block.  Use SCBPTR as the tag
405# value
406
407mk_tag:
408	mvi	DINDEX, MSG_START+1
409	test	SCBARRAY+0,TAG_ENB jz mk_tag_done
410	and	A,0x23,SCBARRAY+0
411	mov	DINDIR,A
412	mov	DINDIR,SCBPTR
413
414	add	MSG_LEN,-MSG_START+0,DINDEX	# update message length
415
416mk_tag_done:
417
418	mov	DINDEX	call mk_dtr	# build DTR message if needed
419
420!message:
421	jmp	poll_for_work
422
423#  Reselection has been initiated by a target. Make a note that we've been
424#  reselected, but haven't seen an IDENTIFY message from the target
425#  yet.
426#
427reselect:
428	mov	SELID		call initialize_scsiid
429	and	FLAGS,0x3f			# reselected, no IDENTIFY	
430	or	FLAGS,RESELECTED jmp select2
431
432# After the selection, remove this SCB from the "waiting for selection"
433# list.  This is achieved by simply moving our "next" pointer into
434# WAITING_SCBH and setting our next pointer to null so that the next
435# time this SCB is used, we don't get confused.
436#
437select:
438	or	SCBARRAY+0,NEEDDMA
439	mov	WAITING_SCBH,SCBARRAY+30
440	mvi	SCBARRAY+30,SCB_LIST_NULL
441select2:
442	call	initialize_for_target
443	mvi	SCSISEQ,ENRSELI
444	mvi	CLRSINT0,0x60			# CLRSELDI|CLRSELDO
445	mvi	CLRSINT1,0x8			# CLRBUSFREE
446
447#  Main loop for information transfer phases.  If BSY is false, then
448#  we have a bus free condition, expected or not.  Otherwise, wait
449#  for the target to assert REQ before checking MSG, C/D and I/O
450#  for the bus phase.
451#
452#  We can't simply look at the values of SCSISIGI here (if we want
453#  to do synchronous data transfer), because the target won't assert
454#  REQ if it's already sent us some data that we haven't acknowledged
455#  yet.
456#
457ITloop:
458	test	SSTAT1,0x8	jnz p_busfree	# BUSFREE
459	test	SSTAT1,0x1	jz ITloop	# REQINIT
460
461	and	A,0xe0,SCSISIGI			# CDI|IOI|MSGI
462
463	cmp	ALLZEROS,A	je p_dataout
464	cmp	A,0x40		je p_datain
465	cmp	A,0x80		je p_command
466	cmp	A,0xc0		je p_status
467	cmp	A,0xa0		je p_mesgout
468	cmp	A,0xe0		je p_mesgin
469
470	mvi	INTSTAT,BAD_PHASE		# unknown - signal driver
471
472p_dataout:
473	mvi	0		call scsisig	# !CDO|!IOO|!MSGO
474	call	assert
475	call	sg_load
476
477	mvi	DINDEX,HADDR
478	mvi	SCBARRAY+19	call bcopy_4
479
480#	mvi	DINDEX,HCNT	# implicit since HCNT is next to HADDR
481	mvi	SCBARRAY+23	call bcopy_3
482
483	mvi	DINDEX,STCNT
484	mvi	SCBARRAY+23	call bcopy_3
485
486# If we are the last SG block, don't set wideodd.
487	test    SCBARRAY+18,0xff jnz p_dataout_wideodd
488	mvi	0x3d		call dma	# SCSIEN|SDMAEN|HDMAEN|
489						#   DIRECTION|FIFORESET
490	jmp	p_dataout_rest
491
492p_dataout_wideodd:
493	mvi	0xbd		call dma	# WIDEODD|SCSIEN|SDMAEN|HDMAEN|
494						#   DIRECTION|FIFORESET
495
496p_dataout_rest:
497#  After a DMA finishes, save the final transfer pointer and count
498#  back into the SCB, in case a device disconnects in the middle of
499#  a transfer.  Use SHADDR and STCNT instead of HADDR and HCNT, since
500#  it's a reflection of how many bytes were transferred on the SCSI
501#  (as opposed to the host) bus.
502#
503	mvi	DINDEX,SCBARRAY+23
504	mvi	STCNT		call bcopy_3
505
506	mvi	DINDEX,SCBARRAY+19
507	mvi	SHADDR		call bcopy_4
508
509	call	sg_advance
510	mov	SCBARRAY+18,SG_COUNT		# residual S/G count
511
512	jmp	ITloop
513
514p_datain:
515	mvi	0x40		call scsisig	# !CDO|IOO|!MSGO
516	call	assert
517	call	sg_load
518
519	mvi	DINDEX,HADDR
520	mvi	SCBARRAY+19	call bcopy_4
521
522#	mvi	DINDEX,HCNT	# implicit since HCNT is next to HADDR
523	mvi	SCBARRAY+23	call bcopy_3
524
525	mvi	DINDEX,STCNT
526	mvi	SCBARRAY+23	call bcopy_3
527
528# If we are the last SG block, don't set wideodd.
529	test	SCBARRAY+18,0xff jnz p_datain_wideodd
530	mvi	0x39		call dma	# SCSIEN|SDMAEN|HDMAEN|
531						#   !DIRECTION|FIFORESET
532	jmp	p_datain_rest
533p_datain_wideodd:
534	mvi	0xb9		call dma	# WIDEODD|SCSIEN|SDMAEN|HDMAEN|
535						#   !DIRECTION|FIFORESET
536p_datain_rest:
537	mvi	DINDEX,SCBARRAY+23
538	mvi	STCNT		call bcopy_3
539
540	mvi	DINDEX,SCBARRAY+19
541	mvi	SHADDR		call bcopy_4
542
543	call	sg_advance
544	mov	SCBARRAY+18,SG_COUNT		# residual S/G count
545
546	jmp	ITloop
547
548#  Command phase.  Set up the DMA registers and let 'er rip - the
549#  two bytes after the SCB SCSI_cmd_length are zeroed by the driver,
550#  so we can copy those three bytes directly into HCNT.
551#
552p_command:
553	mvi	0x80		call scsisig	# CDO|!IOO|!MSGO
554	call	assert
555
556	mvi	DINDEX,HADDR
557	mvi	SCBARRAY+7	call bcopy_4
558
559#	mvi	DINDEX,HCNT	# implicit since HCNT is next to HADDR
560	mvi	SCBARRAY+11	call bcopy_3
561
562	mvi	DINDEX,STCNT
563	mvi	SCBARRAY+11	call bcopy_3
564
565	mvi	0x3d		call dma	# SCSIEN|SDMAEN|HDMAEN|
566						#   DIRECTION|FIFORESET
567	jmp	ITloop
568
569#  Status phase.  Wait for the data byte to appear, then read it
570#  and store it into the SCB.
571#
572p_status:
573	mvi	0xc0		call scsisig	# CDO|IOO|!MSGO
574
575	mvi	SCBARRAY+14	call inb_first
576	jmp	p_mesgin_done
577
578#  Message out phase.  If there is no active message, but the target
579#  took us into this phase anyway, build a no-op message and send it.
580#
581p_mesgout:
582	mvi	0xa0		call scsisig	# CDO|!IOO|MSGO
583	mvi	0x8		call mk_mesg	# build NOP message
584
585	clr     STCNT+2
586	clr     STCNT+1
587
588#  Set up automatic PIO transfer from MSG_START.  Bit 3 in
589#  SXFRCTL0 (SPIOEN) is already on.
590#
591	mvi	SINDEX,MSG_START+0
592	mov	DINDEX,MSG_LEN
593
594#  When target asks for a byte, drop ATN if it's the last one in
595#  the message.  Otherwise, keep going until the message is exhausted.
596#  (We can't use outb for this since it wants the input in SINDEX.)
597#
598#  Keep an eye out for a phase change, in case the target issues
599#  a MESSAGE REJECT.
600#
601p_mesgout2:
602	test	SSTAT0,0x2	jz p_mesgout2	# SPIORDY
603	test	SSTAT1,0x10	jnz p_mesgout6	# PHASEMIS
604
605	cmp	DINDEX,1	jne p_mesgout3	# last byte?
606	mvi	CLRSINT1,0x40			# CLRATNO - drop ATN
607
608#  Write a byte to the SCSI bus.  The AIC-7770 refuses to automatically
609#  send ACKs in automatic PIO or DMA mode unless you make sure that the
610#  "expected" bus phase in SCSISIGO matches the actual bus phase.  This
611#  behaviour is completely undocumented and caused me several days of
612#  grief.
613#
614#  After plugging in different drives to test with and using a longer
615#  SCSI cable, I found that I/O in Automatic PIO mode ceased to function,
616#  especially when transferring >1 byte.  It seems to be much more stable
617#  if STCNT is set to one before the transfer, and SDONE (in SSTAT0) is
618#  polled for transfer completion - for both output _and_ input.  The
619#  only theory I have is that SPIORDY doesn't drop right away when SCSIDATL
620#  is accessed (like the documentation says it does), and that on a longer
621#  cable run, the sequencer code was fast enough to loop back and see
622#  an SPIORDY that hadn't dropped yet.
623#
624p_mesgout3:
625	mvi	STCNT+0, 0x01	
626	mov	SCSIDATL,SINDIR
627
628p_mesgout4:
629	test	SSTAT0,0x4	jz p_mesgout4	# SDONE
630	dec	DINDEX
631	test	DINDEX,0xff	jnz p_mesgout2
632
633#  If the next bus phase after ATN drops is a message out, it means
634#  that the target is requesting that the last message(s) be resent.
635#
636p_mesgout5:
637	test	SSTAT1,0x8	jnz p_mesgout6	# BUSFREE
638	test	SSTAT1,0x1	jz p_mesgout5	# REQINIT
639
640	and	A,0xe0,SCSISIGI			# CDI|IOI|MSGI
641	cmp	A,0xa0		jne p_mesgout6
642	mvi	0x10		call scsisig	# ATNO - re-assert ATN
643
644	jmp	ITloop
645
646p_mesgout6:
647	mvi	CLRSINT1,0x40			# CLRATNO - in case of PHASEMIS
648	and	FLAGS,0xdf			# no active msg
649	jmp	ITloop
650
651#  Message in phase.  Bytes are read using Automatic PIO mode, but not
652#  using inb.  This alleviates a race condition, namely that if ATN had
653#  to be asserted under Automatic PIO mode, it had to beat the SCSI
654#  circuitry sending an ACK to the target.  This showed up under heavy
655#  loads and really confused things, since ABORT commands wouldn't be
656#  seen by the drive after an IDENTIFY message in until it had changed
657#  to a data I/O phase.
658#
659p_mesgin:
660	mvi	0xe0		call scsisig	# CDO|IOO|MSGO
661	mvi	A		call inb_first	# read the 1st message byte
662	mvi	REJBYTE,A			# save it for the driver
663
664	cmp	ALLZEROS,A	jne p_mesgin1
665
666#  We got a "command complete" message, so put the SCB pointer
667#  into the Queue Out, and trigger a completion interrupt.
668#  Check status for non zero return and interrupt driver if needed
669#  This allows the driver to interpret errors only when they occur
670#  instead of always uploading the scb.  If the status is SCSI_CHECK,
671#  the driver will download a new scb requesting sense to replace
672#  the old one, modify the "waiting for selection" SCB list and set 
673#  RETURN_1 to 0x80.  If RETURN_1 is set to 0x80 the sequencer imediately
674#  jumps to main loop where it will run down the waiting SCB list.
675#  If the kernel driver does not wish to request sense, it need
676#  only clear RETURN_1, and the command is allowed to complete.  We don't 
677#  bother to post to the QOUTFIFO in the error case since it would require 
678#  extra work in the kernel driver to ensure that the entry was removed 
679#  before the command complete code tried processing it.
680
681# First check for residuals
682	test	SCBARRAY+15,0xff	jnz resid
683	test	SCBARRAY+16,0xff	jnz resid
684	test	SCBARRAY+17,0xff	jnz resid
685
686check_status:
687	test	SCBARRAY+14,0xff	jz status_ok	# 0 Status?
688	mvi	INTSTAT,BAD_STATUS			# let driver know
689	test	RETURN_1, 0x80	jz status_ok
690	jmp	p_mesgin_done
691
692status_ok:
693#  First, mark this target as free.
694	test	SCBARRAY+0,0x20	jnz complete		# Tagged command
695	and	FUNCTION1,0x70,SCBARRAY+1
696	mov	A,FUNCTION1
697	test	SCBARRAY+1,0x88 jz clear_a
698	xor	ACTIVE_B,A
699	jmp	complete
700
701clear_a:
702	xor	ACTIVE_A,A
703
704	test    SCBARRAY+11,0xff jnz complete  # Immediate message complete
705# Pause the sequencer until the driver gets around to handling the command
706# complete.  This is so that any action that might require carefull timing
707# with the completion of this command can occur.
708	mvi	INTSTAT,IMMEDDONE
709	jmp	start
710complete:
711	mov	QOUTFIFO,SCBPTR
712	mvi	INTSTAT,CMDCMPLT
713	jmp	p_mesgin_done
714
715# If we have a residual count, interrupt and tell the host.  Other
716# alternatives are to pause the sequencer on all command completes (yuck),
717# dma the resid directly to the host (slick, but a ton of instructions), or
718# have the sequencer pause itself when it encounters a non-zero resid 
719# (unecessary pause just to flag the command -- yuck, but takes few instructions
720# and since it shouldn't happen that often is good enough for our purposes).  
721
722resid:
723	mvi	INTSTAT,RESIDUAL
724	jmp	check_status
725
726#  Is it an extended message?  We only support the synchronous and wide data
727#  transfer request messages, which will probably be in response to
728#  WDTR or SDTR message outs from us.  If it's not SDTR or WDTR, reject it -
729#  apparently this can be done after any message in byte, according
730#  to the SCSI-2 spec.
731#
732p_mesgin1:
733	cmp	A,1		jne p_mesgin2	# extended message code?
734	
735	mvi	ARG_1		call inb_next	# extended message length
736	mvi	A		call inb_next	# extended message code
737
738	cmp	A,1		je p_mesginSDTR	# Syncronous negotiation message
739	cmp	A,3		je p_mesginWDTR # Wide negotiation message
740	jmp	p_mesginN
741
742p_mesginWDTR:
743	cmp	ARG_1,2		jne p_mesginN	# extended mesg length = 2
744	mvi	A		call inb_next	# Width of bus
745	mvi	INTSTAT,MSG_WDTR		# let driver know
746	test	RETURN_1,0x80	jz p_mesgin_done# Do we need to send WDTR?
747
748# We didn't initiate the wide negotiation, so we must respond to the request
749	and	RETURN_1,0x7f			# Clear the SEND_WDTR Flag
750	or	FLAGS,ACTIVE_MSG
751	mvi	DINDEX,MSG_START+0
752	mvi	MSG_START+0	call mk_wdtr	# build WDTR message	
753	or	SINDEX,0x10,SIGSTATE		# turn on ATNO
754	call	scsisig
755	jmp	p_mesgin_done
756
757p_mesginSDTR:
758	cmp	ARG_1,3		jne p_mesginN	# extended mesg length = 3
759	mvi	ARG_1		call inb_next	# xfer period
760	mvi	A		call inb_next	# REQ/ACK offset
761	mvi	INTSTAT,MSG_SDTR		# call driver to convert
762
763	test	RETURN_1,0xc0	jz p_mesgin_done# Do we need to mk_sdtr or rej?
764	test	RETURN_1,0x40	jnz p_mesginN	# Requested SDTR too small - rej
765	or	FLAGS,ACTIVE_MSG
766	mvi	DINDEX, MSG_START+0
767	mvi     MSG_START+0     call mk_sdtr
768	or	SINDEX,0x10,SIGSTATE		# turn on ATNO
769	call	scsisig
770	jmp	p_mesgin_done
771
772#  Is it a disconnect message?  Set a flag in the SCB to remind us
773#  and await the bus going free.
774#
775p_mesgin2:
776	cmp	A,4		jne p_mesgin3	# disconnect code?
777
778	or	SCBARRAY+0,0x4			# set "disconnected" bit
779	jmp	p_mesgin_done
780
781#  Save data pointers message?  Copy working values into the SCB,
782#  usually in preparation for a disconnect.
783#
784p_mesgin3:
785	cmp	A,2		jne p_mesgin4	# save data pointers code?
786
787	call	sg_ram2scb
788	jmp	p_mesgin_done
789
790#  Restore pointers message?  Data pointers are recopied from the
791#  SCB anyway at the start of any DMA operation, so the only thing
792#  to copy is the scatter-gather values.
793#
794p_mesgin4:
795	cmp	A,3		jne p_mesgin5	# restore pointers code?
796
797	call	sg_scb2ram
798	jmp	p_mesgin_done
799
800#  Identify message?  For a reconnecting target, this tells us the lun
801#  that the reconnection is for - find the correct SCB and switch to it,
802#  clearing the "disconnected" bit so we don't "find" it by accident later.
803#
804p_mesgin5:
805	test	A,0x80		jz p_mesgin6	# identify message?
806
807	test	A,0x78		jnz p_mesginN	# !DiscPriv|!LUNTAR|!Reserved
808
809	and	A,0x07				# lun in lower three bits
810	or      SAVED_TCL,A,SELID          
811	and     SAVED_TCL,0xf7
812	and     A,0x08,SBLKCTL			# B Channel??
813	or      SAVED_TCL,A
814	call	inb_last			# ACK
815	mov	ALLZEROS	call findSCB    
816setup_SCB:
817	and	SCBARRAY+0,0xfb			# clear disconnect bit in SCB
818	or	FLAGS,IDENTIFY_SEEN		# make note of IDENTIFY
819
820	call	sg_scb2ram			# implied restore pointers
821						#   required on reselect
822	jmp	ITloop
823get_tag:
824	mvi	A		call inb_first
825	cmp	A,0x20  	jne return	# Simple Tag message?
826	mvi	A		call inb_next
827	call			inb_last
828	test	A,0xf0		jnz abort_tag	# Tag in range?
829	mov	SCBPTR,A
830	mov	A,SAVED_TCL
831	cmp	SCBARRAY+1,A		jne abort_tag
832	test	SCBARRAY+0,TAG_ENB	jz  abort_tag
833	ret
834abort_tag:
835	or	SINDEX,0x10,SIGSTATE		# turn on ATNO
836	call	scsisig
837	mvi	INTSTAT,ABORT_TAG 		# let driver know
838	mvi	0xd		call mk_mesg	# ABORT TAG message
839	ret
840
841#  Message reject?  Let the kernel driver handle this.  If we have an 
842#  outstanding WDTR or SDTR negotiation, assume that it's a response from 
843#  the target selecting 8bit or asynchronous transfer, otherwise just ignore 
844#  it since we have no clue what it pertains to.
845#
846p_mesgin6:
847	cmp	A,7		jne p_mesgin7	# message reject code?
848
849	mvi	INTSTAT, MSG_REJECT
850	jmp	p_mesgin_done
851
852#  [ ADD MORE MESSAGE HANDLING HERE ]
853#
854p_mesgin7:
855
856#  We have no idea what this message in is, and there's no way
857#  to pass it up to the kernel, so we issue a message reject and
858#  hope for the best.  Since we're now using manual PIO mode to
859#  read in the message, there should no longer be a race condition
860#  present when we assert ATN.  In any case, rejection should be a
861#  rare occurrence - signal the driver when it happens.
862#
863p_mesginN:
864	or	SINDEX,0x10,SIGSTATE		# turn on ATNO
865	call	scsisig
866	mvi	INTSTAT,SEND_REJECT		# let driver know
867
868	mvi	0x7		call mk_mesg	# MESSAGE REJECT message
869
870p_mesgin_done:
871	call	inb_last			# ack & turn auto PIO back on
872	jmp	ITloop
873
874
875#  Bus free phase.  It might be useful to interrupt the device
876#  driver if we aren't expecting this.  For now, make sure that
877#  ATN isn't being asserted and look for a new command.
878#
879p_busfree:
880	mvi	CLRSINT1,0x40			# CLRATNO
881	clr	SIGSTATE
882
883#  if this is an immediate command, perform a psuedo command complete to
884#  notify the driver.
885	test	SCBARRAY+11,0xff	jz status_ok
886	jmp	start
887
888#  Instead of a generic bcopy routine that requires an argument, we unroll
889#  the two cases that are actually used, and call them explicitly.  This
890#  not only reduces the overhead of doing a bcopy by 2/3rds, but ends up
891#  saving space in the program since you don't have to put the argument 
892#  into the accumulator before the call.  Both functions expect DINDEX to
893#  contain the destination address and SINDEX to contain the source 
894#  address.
895bcopy_3:
896	mov	DINDIR,SINDIR
897	mov	DINDIR,SINDIR
898	mov	DINDIR,SINDIR	ret
899
900bcopy_4:
901	mov	DINDIR,SINDIR
902	mov	DINDIR,SINDIR
903	mov	DINDIR,SINDIR
904	mov	DINDIR,SINDIR	ret
905	
906bcopy_3_dfdat:
907	mov	DINDIR,DFDAT
908	mov	DINDIR,DFDAT
909	mov	DINDIR,DFDAT	ret
910
911bcopy_4_dfdat:
912	mov	DINDIR,DFDAT
913	mov	DINDIR,DFDAT
914	mov	DINDIR,DFDAT
915	mov	DINDIR,DFDAT	ret
916
917#  Locking the driver out, build a one-byte message passed in SINDEX
918#  if there is no active message already.  SINDEX is returned intact.
919#
920mk_mesg:
921	mvi	SEQCTL,0x50			# PAUSEDIS|FASTMODE
922	test	FLAGS,ACTIVE_MSG jnz mk_mesg1	# active message?
923
924	or	FLAGS,ACTIVE_MSG		# if not, there is now
925	mvi	MSG_LEN,1			# length = 1
926	mov	MSG_START+0,SINDEX		# 1-byte message
927
928mk_mesg1:
929	mvi	SEQCTL,0x10	ret		# !PAUSEDIS|FASTMODE
930
931#  Carefully read data in Automatic PIO mode.  I first tried this using
932#  Manual PIO mode, but it gave me continual underrun errors, probably
933#  indicating that I did something wrong, but I feel more secure leaving
934#  Automatic PIO on all the time.
935#
936#  According to Adaptec's documentation, an ACK is not sent on input from
937#  the target until SCSIDATL is read from.  So we wait until SCSIDATL is
938#  latched (the usual way), then read the data byte directly off the bus
939#  using SCSIBUSL.  When we have pulled the ATN line, or we just want to
940#  acknowledge the byte, then we do a dummy read from SCISDATL.  The SCSI
941#  spec guarantees that the target will hold the data byte on the bus until
942#  we send our ACK.
943#
944#  The assumption here is that these are called in a particular sequence,
945#  and that REQ is already set when inb_first is called.  inb_{first,next}
946#  use the same calling convention as inb.
947#
948inb_first:
949	clr	STCNT+2
950	clr	STCNT+1
951	mov	DINDEX,SINDEX
952	mov	DINDIR,SCSIBUSL	ret		# read byte directly from bus
953
954inb_next:
955	mov	DINDEX,SINDEX			# save SINDEX
956
957        mvi     STCNT+0,1			# xfer one byte
958	mov	NONE,SCSIDATL			# dummy read from latch to ACK
959inb_next1:
960	test	SSTAT0,0x4	jz inb_next1	# SDONE
961inb_next2:
962	test	SSTAT0,0x2	jz inb_next2	# SPIORDY - wait for next byte
963	mov	DINDIR,SCSIBUSL	ret		# read byte directly from bus
964
965inb_last:
966	mvi	STCNT+0,1			# ACK with dummy read
967	mov	NONE,SCSIDATL
968inb_last1:
969	test	SSTAT0,0x4	jz inb_last1	# wait for completion
970	ret
971
972#  DMA data transfer.  HADDR and HCNT must be loaded first, and
973#  SINDEX should contain the value to load DFCNTRL with - 0x3d for
974#  host->scsi, or 0x39 for scsi->host.  The SCSI channel is cleared
975#  during initialization.
976#
977dma:
978	mov	DFCNTRL,SINDEX
979dma1:
980dma2:
981	test	SSTAT0,0x1	jnz dma3	# DMADONE
982	test	SSTAT1,0x10	jz dma1		# PHASEMIS, ie. underrun
983
984#  We will be "done" DMAing when the transfer count goes to zero, or
985#  the target changes the phase (in light of this, it makes sense that
986#  the DMA circuitry doesn't ACK when PHASEMIS is active).  If we are
987#  doing a SCSI->Host transfer, the data FIFO should be flushed auto-
988#  magically on STCNT=0 or a phase change, so just wait for FIFO empty
989#  status.
990#
991dma3:
992	test	SINDEX,0x4	jnz dma5	# DIRECTION
993dma4:
994	test	DFSTATUS,0x1	jz dma4		# !FIFOEMP
995
996#  Now shut the DMA enables off, and copy STCNT (ie. the underrun
997#  amount, if any) to the SCB registers; SG_COUNT will get copied to
998#  the SCB's residual S/G count field after sg_advance is called.  Make
999#  sure that the DMA enables are actually off first lest we get an ILLSADDR.
1000#
1001dma5:
1002	clr	DFCNTRL				# disable DMA
1003dma6:
1004	test	DFCNTRL,0x38	jnz dma6	# SCSIENACK|SDMAENACK|HDMAENACK
1005
1006	mvi	DINDEX,SCBARRAY+15
1007	mvi	STCNT		call bcopy_3
1008
1009	ret
1010
1011dma_finish:
1012	test	DFSTATUS,0x8	jz dma_finish	# HDONE
1013
1014	clr	DFCNTRL				# disable DMA
1015dma_finish2:
1016	test	DFCNTRL,0x8	jnz dma_finish2	# HDMAENACK
1017	ret
1018
1019#  Common SCSI initialization for selection and reselection.  Expects
1020#  the target SCSI ID to be in the upper four bits of SINDEX, and A's
1021#  contents are stomped on return.
1022#
1023initialize_scsiid:
1024	and	SINDEX,0xf0		# Get target ID
1025	and	A,0x0f,SCSIID
1026	or	SINDEX,A
1027	mov	SCSIID,SINDEX ret
1028
1029initialize_for_target:
1030#  Turn on Automatic PIO mode now, before we expect to see a REQ
1031#  from the target.  It shouldn't hurt anything to leave it on.  Set
1032#  CLRCHN here before the target has entered a data transfer mode -
1033#  with synchronous SCSI, if you do it later, you blow away some
1034#  data in the SCSI FIFO that the target has already sent to you.
1035#
1036	clr	SIGSTATE 
1037
1038	mvi	SXFRCTL0,0x8a			# DFON|SPIOEN|CLRCHN
1039
1040#  Initialize scatter-gather pointers by setting up the working copy
1041#  in scratch RAM.
1042#
1043	call	sg_scb2ram
1044
1045#  Initialize SCSIRATE with the appropriate value for this target.
1046#
1047	call	ndx_dtr
1048	mov	SCSIRATE,SINDIR	ret
1049
1050#  Assert that if we've been reselected, then we've seen an IDENTIFY
1051#  message.
1052#
1053assert:
1054	test	FLAGS,RESELECTED	jz return	# reselected?
1055	test	FLAGS,IDENTIFY_SEEN	jnz return	# seen IDENTIFY?
1056
1057	mvi	INTSTAT,NO_IDENT 	ret	# no - cause a kernel panic
1058
1059#  Find out if disconnection is ok from the information the BIOS has left
1060#  us.  The tcl from SCBARRAY+1 should be in SINDEX; A will
1061#  contain either 0x40 (disconnection ok) or 0x00 (disconnection not ok)
1062#  on exit.
1063#
1064#  To allow for wide or twin busses, we check the upper bit of the target ID
1065#  and the channel ID and look at the appropriate disconnect register. 
1066#
1067disconnect:
1068	and	FUNCTION1,0x70,SINDEX		# strip off extra just in case
1069	mov	A,FUNCTION1
1070	test	SINDEX, 0x88	jz disconnect_a
1071
1072	test	DISC_DSB_B,A	jz disconnect1	# bit nonzero if DISabled
1073	clr	A		ret
1074
1075disconnect_a:
1076	test	DISC_DSB_A,A	jz disconnect1	# bit nonzero if DISabled
1077	clr	A		ret
1078
1079disconnect1:
1080	mvi	A,0x40		ret
1081
1082#  Locate the SCB matching the target ID/channel/lun in SAVED_TCL and switch 
1083#  the SCB to it.  Have the kernel print a warning message if it can't be 
1084#  found, and generate an ABORT message to the target.  SINDEX should be
1085#  cleared on call.
1086#
1087findSCB:
1088	mov	A,SAVED_TCL
1089	mov	SCBPTR,SINDEX			# switch to new SCB
1090	cmp	SCBARRAY+1,A	jne findSCB1	# target ID/channel/lun match?
1091	test	SCBARRAY+0,0x4	jz findSCB1	# should be disconnected
1092	test	SCBARRAY+0,TAG_ENB jnz get_tag
1093	ret
1094
1095findSCB1:
1096	inc	SINDEX
1097	mov	A,SCBCOUNT
1098	cmp	SINDEX,A	jne findSCB
1099
1100	mvi	INTSTAT,NO_MATCH		# not found - signal kernel
1101	mvi	0x6		call mk_mesg	# ABORT message
1102
1103	or	SINDEX,0x10,SIGSTATE		# assert ATNO
1104	call	scsisig
1105	ret
1106
1107#  Make a working copy of the scatter-gather parameters in the SCB.
1108#
1109sg_scb2ram:
1110	mov	SG_COUNT,SCBARRAY+2
1111
1112	mvi	DINDEX,SG_NEXT
1113	mvi	SCBARRAY+3	call bcopy_4
1114
1115	mvi	SG_NOLOAD,0x80
1116	test	SCBARRAY+0,0x10	jnz return	# don't reload s/g?
1117	clr	SG_NOLOAD	 ret
1118
1119#  Copying RAM values back to SCB, for Save Data Pointers message.
1120#
1121sg_ram2scb:
1122	mov	SCBARRAY+2,SG_COUNT
1123
1124	mvi	DINDEX,SCBARRAY+3
1125	mvi	SG_NEXT		call bcopy_4
1126
1127	and	SCBARRAY+0,0xef,SCBARRAY+0
1128	test	SG_NOLOAD,0x80	jz return	# reload s/g?
1129	or	SCBARRAY+0,SG_LOAD	 ret
1130
1131#  Load a struct scatter if needed and set up the data address and
1132#  length.  If the working value of the SG count is nonzero, then
1133#  we need to load a new set of values.
1134#
1135#  This, like the above DMA, assumes a little-endian host data storage.
1136#
1137sg_load:
1138	test	SG_COUNT,0xff	jz return	# SG being used?
1139	test	SG_NOLOAD,0x80	jnz return	# don't reload s/g?
1140
1141	clr	HCNT+2
1142	clr	HCNT+1
1143	mvi	HCNT+0,SG_SIZEOF
1144
1145	mvi	DINDEX,HADDR
1146	mvi	SG_NEXT		call bcopy_4
1147
1148	mvi	DFCNTRL,0xd			# HDMAEN|DIRECTION|FIFORESET
1149
1150#  Wait for DMA from host memory to data FIFO to complete, then disable
1151#  DMA and wait for it to acknowledge that it's off.
1152#
1153
1154	call	dma_finish
1155
1156#  Copy data from FIFO into SCB data pointer and data count.  This assumes
1157#  that the struct scatterlist has this structure (this and sizeof(struct
1158#  scatterlist) == 12 are asserted in aic7xxx.c):
1159#
1160#	struct scatterlist {
1161#		char *address;		/* four bytes, little-endian order */
1162#		...			/* four bytes, ignored */
1163#		unsigned short length;	/* two bytes, little-endian order */
1164#	}
1165#
1166
1167# Not in FreeBSD.  the scatter list entry is only 8 bytes.
1168# 
1169# struct ahc_dma_seg {
1170#       physaddr addr;                  /* four bytes, little-endian order */
1171#       long    len;                    /* four bytes, little endian order */   
1172# };
1173#
1174
1175	mvi	DINDEX, SCBARRAY+19
1176	call	bcopy_4_dfdat
1177
1178# For Linux, we must throw away four bytes since there is a 32bit gap
1179# in the middle of a struct scatterlist
1180#	mov	NONE,DFDAT
1181#	mov	NONE,DFDAT
1182#	mov	NONE,DFDAT
1183#	mov	NONE,DFDAT
1184
1185	call	bcopy_3_dfdat		#Only support 24 bit length.
1186	ret
1187
1188#  Advance the scatter-gather pointers only IF NEEDED.  If SG is enabled,
1189#  and the SCSI transfer count is zero (note that this should be called
1190#  right after a DMA finishes), then move the working copies of the SG
1191#  pointer/length along.  If the SCSI transfer count is not zero, then
1192#  presumably the target is disconnecting - do not reload the SG values
1193#  next time.
1194#
1195sg_advance:
1196	test	SG_COUNT,0xff	jz return	# s/g enabled?
1197
1198	test	STCNT+0,0xff	jnz sg_advance1	# SCSI transfer count nonzero?
1199	test	STCNT+1,0xff	jnz sg_advance1
1200	test	STCNT+2,0xff	jnz sg_advance1
1201
1202	clr	SG_NOLOAD			# reload s/g next time
1203	dec	SG_COUNT			# one less segment to go
1204
1205	clr	A				# add sizeof(struct scatter)
1206	add	SG_NEXT+0,SG_SIZEOF,SG_NEXT+0
1207	adc	SG_NEXT+1,A,SG_NEXT+1
1208	adc	SG_NEXT+2,A,SG_NEXT+2
1209	adc	SG_NEXT+3,A,SG_NEXT+3	ret
1210
1211sg_advance1:
1212	mvi	SG_NOLOAD,0x80	ret		# don't reload s/g next time
1213
1214#  Add the array base SYNCNEG to the target offset (the target address
1215#  is in SCSIID), and return the result in SINDEX.  The accumulator
1216#  contains the 3->8 decoding of the target ID on return.
1217#
1218ndx_dtr:
1219	shr	A,SCSIID,4
1220	test	SBLKCTL,0x08	jz ndx_dtr_2
1221	or	A,0x08		# Channel B entries add 8
1222ndx_dtr_2:
1223	add	SINDEX,SYNCNEG,A
1224
1225	and	FUNCTION1,0x70,SCSIID		# 3-bit target address decode
1226	mov	A,FUNCTION1	ret
1227
1228#  If we need to negotiate transfer parameters, build the WDTR or SDTR message
1229#  starting at the address passed in SINDEX.  DINDEX is modified on return.
1230#  The SCSI-II spec requires that Wide negotiation occur first and you can
1231#  only negotiat one or the other at a time otherwise in the event of a message
1232#  reject, you wouldn't be able to tell which message was the culpret.
1233#
1234mk_dtr:
1235	test	SCBARRAY+0,0xc0 jz return	# NEEDWDTR|NEEDSDTR
1236	test	SCBARRAY+0,NEEDWDTR jnz  mk_wdtr_16bit
1237	or	FLAGS, MAX_OFFSET	# Force an offset of 15 or 8 if WIDE
1238
1239mk_sdtr:
1240	mvi	DINDIR,1			# extended message
1241	mvi	DINDIR,3			# extended message length = 3
1242	mvi	DINDIR,1			# SDTR code
1243	call	sdtr_to_rate
1244	mov	DINDIR,RETURN_1			# REQ/ACK transfer period
1245	test	FLAGS, MAX_OFFSET jnz mk_sdtr_max_offset
1246	and	DINDIR,0x0f,SINDIR		# Sync Offset
1247
1248mk_sdtr_done:
1249	add	MSG_LEN,-MSG_START+0,DINDEX ret	# update message length
1250
1251mk_sdtr_max_offset:
1252# We're initiating sync negotiation, so request the max offset we can (15 or 8)
1253	xor	FLAGS, MAX_OFFSET
1254	test	SCSIRATE, 0x80	jnz wmax_offset	# Talking to a WIDE device?
1255	mvi	DINDIR, MAX_OFFSET_8BIT
1256	jmp	mk_sdtr_done
1257
1258wmax_offset:
1259	mvi	DINDIR, MAX_OFFSET_WIDE
1260	jmp	mk_sdtr_done
1261
1262mk_wdtr_16bit:
1263	mvi	ARG_1,BUS_16_BIT
1264mk_wdtr:
1265	mvi	DINDIR,1			# extended message
1266	mvi	DINDIR,2			# extended message length = 2
1267	mvi	DINDIR,3			# WDTR code
1268	mov	DINDIR,ARG_1			# bus width
1269
1270	add	MSG_LEN,-MSG_START+0,DINDEX ret	# update message length
1271	
1272#  Set SCSI bus control signal state.  This also saves the last-written
1273#  value into a location where the higher-level driver can read it - if
1274#  it has to send an ABORT or RESET message, then it needs to know this
1275#  so it can assert ATN without upsetting SCSISIGO.  The new value is
1276#  expected in SINDEX.  Change the actual state last to avoid contention
1277#  from the driver.
1278#
1279scsisig:
1280	mov	SIGSTATE,SINDEX
1281	mov	SCSISIGO,SINDEX	ret
1282
1283sdtr_to_rate:
1284	call	ndx_dtr				# index scratch space for target
1285	shr	A,SINDIR,0x4
1286	dec	SINDEX				#Preserve SINDEX
1287	and	A,0x7
1288	clr	RETURN_1
1289sdtr_to_rate_loop:
1290	test	A,0x0f	jz sdtr_to_rate_done
1291	add	RETURN_1,0x18
1292	dec	A	
1293	jmp	sdtr_to_rate_loop
1294sdtr_to_rate_done:
1295	shr	RETURN_1,0x2
1296	add	RETURN_1,0x18	ret
1297
1298return:
1299	ret
1300