aic7xxx.seq revision 15328
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 *FreeBSD, Twin, Wide, 2 command per target support, tagged queuing,
9 *SCB paging and other optimizations:
10 *Copyright (c) 1994, 1995, 1996 Justin Gibbs. All rights reserved.
11 *
12 *Redistribution and use in source and binary forms, with or without
13 *modification, are permitted provided that the following conditions
14 *are met:
15 *1. Redistributions of source code must retain the above copyright
16 *   notice, this list of conditions, and the following disclaimer.
17 *2. Redistributions in binary form must reproduce the above copyright
18 *   notice, this list of conditions and the following disclaimer in the
19 *   documentation and/or other materials provided with the distribution.
20 *3. All advertising materials mentioning features or use of this software
21 *   must display the following acknowledgement:
22 *     This product includes software developed by the University of Calgary
23 *     Department of Computer Science and its contributors.
24 *4. Neither the name of the University nor the names of its contributors
25 *   may be used to endorse or promote products derived from this software
26 *   without specific prior written permission.
27 *
28 *THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
29 *ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
30 *IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
31 *ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
32 *FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
33 *DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
34 *OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
35 *HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
36 *LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
37 *OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
38 *SUCH DAMAGE.
39 *
40 *-M************************************************************************/
41
42VERSION AIC7XXX_SEQ_VER "$Id: aic7xxx.seq,v 1.32 1996/03/31 03:02:33 gibbs Exp $"
43
44#include "../../dev/aic7xxx/aic7xxx_reg.h"
45
46/*
47 * We can't just use ACCUM in the sequencer code because it
48 * must be treated specially by the assembler, and it currently
49 * looks for the symbol 'A'.  This is the only register defined in
50 * the assembler's symbol space.
51 */
52A = ACCUM
53
54/* After starting the selection hardware, we check for reconnecting targets
55 * as well as for our selection to complete just in case the reselection wins
56 * bus arbitration.  The problem with this is that we must keep track of the
57 * SCB that we've already pulled from the QINFIFO and started the selection
58 * on just in case the reselection wins so that we can retry the selection at
59 * a later time.  This problem cannot be resolved by holding a single entry
60 * in scratch ram since a reconnecting target can request sense and this will
61 * create yet another SCB waiting for selection.  The solution used here is to 
62 * use byte 27 of the SCB as a psuedo-next pointer and to thread a list
63 * of SCBs that are awaiting selection.  Since 0-0xfe are valid SCB offsets, 
64 * SCB_LIST_NULL is 0xff which is out of range.  The kernel driver must
65 * add an entry to this list everytime a request sense occurs.  The sequencer
66 * will automatically consume the entries.
67 */
68
69/*
70 * We assume that the kernel driver may reset us at any time, even in the
71 * middle of a DMA, so clear DFCNTRL too.
72 */
73reset:
74	clr	DFCNTRL
75	clr	SCSISIGO		/* De-assert BSY */
76/*
77 * We jump to start after every bus free.
78 */
79start:
80	and	FLAGS,0x0f		/* clear target specific flags */
81	mvi	SCSISEQ,ENRSELI		/* Always allow reselection */
82poll_for_work:
83	/*
84	 * Are we a twin channel device?
85	 * For fairness, we check the other bus first,
86	 * since we just finished a transaction on the
87	 * current channel.
88	 */
89	test	FLAGS,TWIN_BUS	jz start2
90	xor	SBLKCTL,SELBUSB			/* Toggle to the other bus */
91	test	SSTAT0,SELDI	jnz reselect
92	xor	SBLKCTL,SELBUSB			/* Toggle to the original bus */
93start2:
94	test	SSTAT0,SELDI	jnz reselect
95	cmp	WAITING_SCBH,SCB_LIST_NULL jne start_waiting
96	mov	A, QCNTMASK
97	test	QINCNT,A	jz poll_for_work
98
99/*
100 * We have at least one queued SCB now and we don't have any 
101 * SCBs in the list of SCBs awaiting selection.  Set the SCB
102 * pointer from the FIFO so we see the right bank of SCB 
103 * registers.
104 */
105	mov	SCBPTR,QINFIFO
106
107/*
108 * See if there is not already an active SCB for this target.  This code
109 * locks out on a per target basis instead of target/lun.  Although this
110 * is not ideal for devices that have multiple luns active at the same
111 * time, it is faster than looping through all SCB's looking for active
112 * commands.  It may be benificial to make findscb a more general procedure
113 * to see if the added cost of the search is negligible.  This code also 
114 * assumes that the kernel driver will clear the active flags on board 
115 * initialization, board reset, and a target SELTO.  Tagged commands
116 * don't set the active bits since you can queue more than one command
117 * at a time.  We do, however, look to see if there are any non-tagged
118 * I/Os in progress, and requeue the command if there are.  Tagged and
119 * non-tagged commands cannot be mixed to a single target.
120 */
121
122test_busy:
123	mov	FUNCTION1,SCB_TCL
124	mov	A,FUNCTION1
125	test	SCB_TCL,0x88	jz test_a	/* Id < 8 && A channel */
126
127	test	ACTIVE_B,A	jnz requeue
128	test	SCB_CONTROL,TAG_ENB	jnz start_scb
129	/* Mark the current target as busy */
130	or	ACTIVE_B,A
131	jmp	start_scb
132
133/* Place the currently active SCB back on the queue for later processing */
134requeue:
135	mov	QINFIFO, SCBPTR
136	jmp	poll_for_work
137
138/*
139 * Pull the first entry off of the waiting for selection list
140 * We don't have to "test_busy" because only transactions that
141 * have passed that test can be in the waiting_scb list.
142 */
143start_waiting:
144	mov	SCBPTR,WAITING_SCBH
145	jmp	start_scb2
146
147test_a:
148	test	ACTIVE_A,A jnz requeue
149	test	SCB_CONTROL,TAG_ENB jnz start_scb
150	/* Mark the current target as busy */
151	or	ACTIVE_A,A
152
153start_scb:
154	mov	SCB_NEXT,WAITING_SCBH
155	mov	WAITING_SCBH, SCBPTR
156start_scb2:
157	and	SINDEX,0xf7,SBLKCTL	/* Clear the channel select bit */
158	and	A,0x08,SCB_TCL		/* Get new channel bit */
159	or	SINDEX,A
160	mov	SBLKCTL,SINDEX		/* select channel */
161	mov	SCB_TCL	call initialize_scsiid
162
163/*
164 * Enable selection phase as an initiator, and do automatic ATN
165 * after the selection.  We do this now so that we can overlap the
166 * rest of our work to set up this target with the arbitration and
167 * selection bus phases.
168 */
169start_selection:
170	mvi	SCSISEQ,0x58		/* ENSELO|ENAUTOATNO|ENRSELI */
171
172/*
173 * As soon as we get a successful selection, the target should go
174 * into the message out phase since we have ATN asserted.  Prepare
175 * the message to send.
176 *
177 * Messages are stored in scratch RAM starting with a length byte
178 * followed by the message itself.
179 */
180	test	SCB_CMDLEN,0xff jnz mk_identify	/* 0 Length Command? */
181
182/*
183 * The kernel has sent us an SCB with no command attached.  This implies
184 * that the kernel wants to send a message of some sort to this target,
185 * so we interrupt the driver, allow it to fill the message buffer, and
186 * then go back into the arbitration loop
187 */
188	mvi     INTSTAT,AWAITING_MSG
189	jmp     wait_for_selection
190
191mk_identify:
192	and	A,DISCENB,SCB_CONTROL	/* mask off disconnect privledge */
193
194	and	MSG0,0x7,SCB_TCL	/* lun */
195	or	MSG0,A			/* or in disconnect privledge */
196	or	MSG0,MSG_IDENTIFY
197	mvi	MSG_LEN, 1
198
199	test	SCB_CONTROL,0xb0 jz  !message	/* WDTR, SDTR or TAG?? */
200/*
201 * Send a tag message if TAG_ENB is set in the SCB control block.
202 * Use SCB_TAG (the position in the kernel's SCB array) as the tag value.
203 */
204
205mk_tag:
206	mvi	DINDEX, MSG1
207	test	SCB_CONTROL,TAG_ENB jz mk_tag_done
208	and	DINDIR,0x23,SCB_CONTROL
209	mov	DINDIR,SCB_TAG
210
211	add	MSG_LEN,COMP_MSG0,DINDEX	/* update message length */
212
213mk_tag_done:
214
215	test	SCB_CONTROL,0x90 jz !message	/* NEEDWDTR|NEEDSDTR */
216	mov	DINDEX	call mk_dtr	/* build DTR message if needed */
217
218!message:
219wait_for_selection:
220	test	SSTAT0,SELDO	jnz select 
221	test	SSTAT0,SELDI	jz wait_for_selection
222
223/*
224 * Reselection has been initiated by a target. Make a note that we've been
225 * reselected, but haven't seen an IDENTIFY message from the target
226 * yet.
227 */
228reselect:
229	clr	MSG_LEN		/* Don't have anything in the mesg buffer */
230	mov	SELID		call initialize_scsiid
231	or	FLAGS,RESELECTED
232	jmp	select2
233
234/*
235 * After the selection, remove this SCB from the "waiting for selection"
236 * list.  This is achieved by simply moving our "next" pointer into
237 * WAITING_SCBH.  Our next pointer will be set to null the next time this
238 * SCB is used, so don't bother with it now.
239 */
240select:
241	mov	WAITING_SCBH,SCB_NEXT
242	or	FLAGS,SELECTED
243select2:
244/*
245 * Set CLRCHN here before the target has entered a data transfer mode -
246 * with synchronous SCSI, if you do it later, you blow away some
247 * data in the SCSI FIFO that the target has already sent to you.
248 */
249	or	SXFRCTL0,CLRCHN
250/*
251 * Initialize SCSIRATE with the appropriate value for this target.
252 */
253	call	ndx_dtr
254	mov	SCSIRATE,SINDIR
255
256	mvi	SCSISEQ,ENAUTOATNP		/*
257						 * ATN on parity errors
258						 * for "in" phases
259						 */
260	mvi	CLRSINT1,CLRBUSFREE
261	mvi	CLRSINT0,0x60			/* CLRSELDI|CLRSELDO */
262
263/*
264 * Main loop for information transfer phases.  If BSY is false, then
265 * we have a bus free condition, expected or not.  Otherwise, wait
266 * for the target to assert REQ before checking MSG, C/D and I/O
267 * for the bus phase.
268 *
269 */
270ITloop:
271	test	SSTAT1,BUSFREE	jnz p_busfree
272	test	SSTAT1,REQINIT	jz ITloop
273
274	and	A,PHASE_MASK,SCSISIGI
275	mov	LASTPHASE,A
276	mov	SCSISIGO,A
277
278	cmp	ALLZEROS,A	je p_dataout
279	cmp	A,P_DATAIN	je p_datain
280	cmp	A,P_COMMAND	je p_command
281	cmp	A,P_MESGOUT	je p_mesgout
282	cmp	A,P_STATUS	je p_status
283	cmp	A,P_MESGIN	je p_mesgin
284
285	mvi	INTSTAT,BAD_PHASE	/* unknown phase - signal driver */
286
287p_dataout:
288	mvi	DMAPARAMS,0x7d			/*
289						 * WIDEODD|SCSIEN|SDMAEN|HDMAEN|
290						 * DIRECTION|FIFORESET
291						 */
292	jmp	data_phase_init
293
294/*
295 * If we re-enter the data phase after going through another phase, the
296 * STCNT may have been cleared, so restore it from the residual field.
297 */
298data_phase_reinit:
299	mov	STCNT0,SCB_RESID_DCNT0
300	mov	STCNT1,SCB_RESID_DCNT1
301	mov	STCNT2,SCB_RESID_DCNT2
302	jmp	data_phase_loop
303
304p_datain:
305	mvi	DMAPARAMS,0x79		/*
306					 * WIDEODD|SCSIEN|SDMAEN|HDMAEN|
307					 * !DIRECTION|FIFORESET
308					 */
309data_phase_init:
310	call	assert
311
312	test	FLAGS, DPHASE	jnz data_phase_reinit
313	call	sg_scb2ram
314	or	FLAGS, DPHASE		/* We have seen a data phase */
315
316data_phase_loop:
317/* If we are the last SG block, don't set wideodd. */
318	cmp	SG_COUNT,0x01 jne data_phase_wideodd
319	and	DMAPARAMS, 0xbf		/* Turn off WIDEODD */
320data_phase_wideodd:
321	mov	DMAPARAMS  call dma
322
323/* Exit if we had an underrun */
324	test	SSTAT0,SDONE	jz data_phase_finish /* underrun STCNT != 0 */
325
326/*
327 * Advance the scatter-gather pointers if needed 
328 */
329sg_advance:
330	dec	SG_COUNT	/* one less segment to go */
331
332	test	SG_COUNT, 0xff	jz data_phase_finish /* Are we done? */
333
334	clr	A			/* add sizeof(struct scatter) */
335	add	SG_NEXT0,SG_SIZEOF,SG_NEXT0
336	adc	SG_NEXT1,A,SG_NEXT1
337
338/*
339 * Load a struct scatter and set up the data address and length.
340 * If the working value of the SG count is nonzero, then
341 * we need to load a new set of values.
342 *
343 * This, like all DMA's, assumes little-endian host data storage.
344 */
345sg_load:
346	clr	HCNT2
347	clr	HCNT1
348	mvi	HCNT0,SG_SIZEOF
349
350	mov	HADDR0,SG_NEXT0
351	mov	HADDR1,SG_NEXT1
352	mov	HADDR2,SG_NEXT2
353	mov	HADDR3,SG_NEXT3
354
355	or	DFCNTRL,0xd			/* HDMAEN|DIRECTION|FIFORESET */
356
357/*
358 * Wait for DMA from host memory to data FIFO to complete, then disable
359 * DMA and wait for it to acknowledge that it's off.
360 */
361dma_finish:
362	test	DFSTATUS,HDONE	jz dma_finish
363	/* Turn off DMA preserving WIDEODD */
364	and	DFCNTRL,WIDEODD
365dma_finish2:
366	test	DFCNTRL,HDMAENACK jnz dma_finish2
367
368/*
369 * Copy data from FIFO into SCB data pointer and data count.  This assumes
370 * that the struct scatterlist has this structure (this and sizeof(struct
371 * scatterlist) == 12 are asserted in aic7xxx.c for the Linux driver):
372 *
373 *	struct scatterlist {
374 *		char *address;		four bytes, little-endian order
375 *		...			four bytes, ignored
376 *		unsigned short length;	two bytes, little-endian order
377 *	}
378 *
379 *
380 * In FreeBSD, the scatter list entry is only 8 bytes.
381 * 
382 * struct ahc_dma_seg {
383 *       physaddr addr;                  four bytes, little-endian order
384 *       long    len;                    four bytes, little endian order
385 * };
386 */
387
388	mov	HADDR0,DFDAT
389	mov	HADDR1,DFDAT
390	mov	HADDR2,DFDAT
391	mov	HADDR3,DFDAT
392/*
393 * For Linux, we must throw away four bytes since there is a 32bit gap
394 * in the middle of a struct scatterlist.
395 */
396#ifdef linux
397	mov	NONE,DFDAT
398	mov	NONE,DFDAT
399	mov	NONE,DFDAT
400	mov	NONE,DFDAT
401#endif
402	mov	HCNT0,DFDAT
403	mov	HCNT1,DFDAT
404	mov	HCNT2,DFDAT
405
406/* Load STCNT as well.  It is a mirror of HCNT */
407	mov	STCNT0,HCNT0
408	mov	STCNT1,HCNT1
409	mov	STCNT2,HCNT2
410        test    SSTAT1,PHASEMIS  jz data_phase_loop
411
412data_phase_finish:
413/*
414 * After a DMA finishes, save the SG and STCNT residuals back into the SCB
415 * We use STCNT instead of HCNT, since it's a reflection of how many bytes 
416 * were transferred on the SCSI (as opposed to the host) bus.
417 */
418	mov	SCB_RESID_DCNT0,STCNT0
419	mov	SCB_RESID_DCNT1,STCNT1
420	mov	SCB_RESID_DCNT2,STCNT2
421	mov	SCB_RESID_SGCNT, SG_COUNT
422	jmp	ITloop
423
424/*
425 * Command phase.  Set up the DMA registers and let 'er rip.
426 */
427p_command:
428	call	assert
429
430/*
431 * Load HADDR and HCNT.
432 */
433	mov	HADDR0, SCB_CMDPTR0
434	mov	HADDR1, SCB_CMDPTR1
435	mov	HADDR2, SCB_CMDPTR2
436	mov	HADDR3, SCB_CMDPTR3
437	mov	HCNT0, SCB_CMDLEN
438	clr	HCNT1
439	clr	HCNT2
440
441	mov	STCNT0, HCNT0
442	mov	STCNT1, HCNT1
443	mov	STCNT2, HCNT2
444
445	mvi	0x3d		call dma	# SCSIEN|SDMAEN|HDMAEN|
446						#   DIRECTION|FIFORESET
447	jmp	ITloop
448
449/*
450 * Status phase.  Wait for the data byte to appear, then read it
451 * and store it into the SCB.
452 */
453p_status:
454	mvi	SCB_TARGET_STATUS	call inb_first
455	jmp	mesgin_done
456
457/*
458 * Message out phase.  If there is not an active message, but the target
459 * took us into this phase anyway, build a no-op message and send it.
460 */
461p_mesgout:
462	test	MSG_LEN, 0xff	jnz  p_mesgout_start
463	mvi	MSG_NOP		call mk_mesg	/* build NOP message */
464
465p_mesgout_start:
466/*
467 * Set up automatic PIO transfer from MSG0.  Bit 3 in
468 * SXFRCTL0 (SPIOEN) is already on.
469 */
470	mvi	SINDEX,MSG0
471	mov	DINDEX,MSG_LEN
472
473/*
474 * When target asks for a byte, drop ATN if it's the last one in
475 * the message.  Otherwise, keep going until the message is exhausted.
476 *
477 * Keep an eye out for a phase change, in case the target issues
478 * a MESSAGE REJECT.
479 */
480p_mesgout_loop:
481	test	SSTAT1,PHASEMIS	jnz p_mesgout_phasemis
482	test	SSTAT0,SPIORDY	jz p_mesgout_loop
483	cmp	DINDEX,1	jne p_mesgout_outb	/* last byte? */
484	mvi	CLRSINT1,CLRATNO			/* drop ATN */
485p_mesgout_outb:
486	dec	DINDEX
487	or	CLRSINT0, CLRSPIORDY
488	mov	SCSIDATL,SINDIR
489	
490p_mesgout4:
491	test	DINDEX,0xff	jnz p_mesgout_loop
492
493/*
494 * If the next bus phase after ATN drops is a message out, it means
495 * that the target is requesting that the last message(s) be resent.
496 */
497p_mesgout_snoop:
498	test	SSTAT1,BUSFREE	jnz p_mesgout_done
499	test	SSTAT1,REQINIT	jz p_mesgout_snoop
500
501	test	SSTAT1,PHASEMIS	jnz p_mesgout_done
502
503	or	SCSISIGO,ATNO			/* turn on ATNO */
504
505	jmp	ITloop
506
507p_mesgout_phasemis:
508	mvi	CLRSINT1,CLRATNO	/* Be sure to turn ATNO off */
509p_mesgout_done:
510	clr	MSG_LEN			/* no active msg */
511	jmp	ITloop
512
513/*
514 * Message in phase.  Bytes are read using Automatic PIO mode.
515 */
516p_mesgin:
517	mvi	A		call inb_first	/* read the 1st message byte */
518	mov	REJBYTE,A			/* save it for the driver */
519
520	test	A,MSG_IDENTIFY		jnz mesgin_identify
521	cmp	A,MSG_DISCONNECT	je mesgin_disconnect
522	cmp	A,MSG_SDPTRS		je mesgin_sdptrs
523	cmp	ALLZEROS,A		je mesgin_complete
524	cmp	A,MSG_RDPTRS		je mesgin_rdptrs
525	cmp	A,MSG_EXTENDED		je mesgin_extended
526	cmp	A,MSG_REJECT		je mesgin_reject
527
528rej_mesgin:
529/*
530 * We have no idea what this message in is, and there's no way
531 * to pass it up to the kernel, so we issue a message reject and
532 * hope for the best.  Since we're now using manual PIO mode to
533 * read in the message, there should no longer be a race condition
534 * present when we assert ATN.  In any case, rejection should be a
535 * rare occurrence - signal the driver when it happens.
536 */
537	or	SCSISIGO,ATNO			/* turn on ATNO */
538	mvi	INTSTAT,SEND_REJECT		/* let driver know */
539
540	mvi	MSG_REJECT	call mk_mesg
541
542mesgin_done:
543	call	inb_last			/*ack & turn auto PIO back on*/
544	jmp	ITloop
545
546
547mesgin_complete:
548/*
549 * We got a "command complete" message, so put the SCB_TAG into QUEUEOUT,
550 * and trigger a completion interrupt.  Check status for non zero return
551 * and interrupt driver if needed.  This allows the driver to interpret
552 * errors only when they occur instead of always uploading the scb.  If
553 * the status is SCSI_CHECK, the driver will download a new scb requesting
554 * sense to replace the old one, modify the "waiting for selection" SCB list
555 * and set RETURN_1 to SEND_SENSE.  If RETURN_1 is set to SEND_SENSE the
556 * sequencer imediately jumps to main loop where it will run down the waiting
557 * SCB list and process the sense request.  If the kernel driver does not
558 * wish to request sense, it need only clear RETURN_1, and the command is
559 * allowed to complete.  We don't bother to post to the QOUTFIFO in the
560 * error case since it would require extra work in the kernel driver to
561 * ensure that the entry was removed before the command complete code tried
562 * processing it.
563 *
564 * First check for residuals
565 */
566	test	SCB_RESID_SGCNT,0xff	jz check_status
567/*
568 * If we have a residual count, interrupt and tell the host.  Other
569 * alternatives are to pause the sequencer on all command completes (yuck),
570 * dma the resid directly to the host (slick, we may have space to do it now)
571 * or have the sequencer pause itself when it encounters a non-zero resid 
572 * (unecessary pause just to flag the command -yuck-, but takes one instruction
573 * and since it shouldn't happen that often is good enough for our purposes).  
574 */
575resid:
576	mvi	INTSTAT,RESIDUAL
577
578check_status:
579	test	SCB_TARGET_STATUS,0xff	jz status_ok	/* Good Status? */
580	mvi	INTSTAT,BAD_STATUS			/* let driver know */
581	cmp	RETURN_1, SEND_SENSE	jne status_ok
582	jmp	mesgin_done
583
584status_ok:
585/* First, mark this target as free. */
586	test	SCB_CONTROL,TAG_ENB jnz test_immediate	/*
587							 * Tagged commands
588							 * don't busy the
589							 * target.
590							 */
591	mov	FUNCTION1,SCB_TCL
592	mov	A,FUNCTION1
593	test	SCB_TCL,0x88 jz clear_a
594	xor	ACTIVE_B,A
595	jmp	test_immediate
596
597clear_a:
598	xor	ACTIVE_A,A
599
600test_immediate:
601	test    SCB_CMDLEN,0xff jnz complete  /* Immediate message complete */
602/*
603 * Pause the sequencer until the driver gets around to handling the command
604 * complete.  This is so that any action that might require carefull timing
605 * with the completion of this command can occur.
606 */
607	mvi	INTSTAT,IMMEDDONE
608	jmp	start
609complete:
610	mov	QOUTFIFO,SCB_TAG
611	mvi	INTSTAT,CMDCMPLT
612	jmp	mesgin_done
613
614
615/*
616 * Is it an extended message?  We only support the synchronous and wide data
617 * transfer request messages, which will probably be in response to
618 * WDTR or SDTR message outs from us.  If it's not SDTR or WDTR, reject it -
619 * apparently this can be done after any message in byte, according
620 * to the SCSI-2 spec.
621 */
622mesgin_extended:
623	mvi	ARG_1		call inb_next	/* extended message length */
624	mvi	REJBYTE_EXT	call inb_next	/* extended message code */
625
626	cmp	REJBYTE_EXT,MSG_SDTR	je p_mesginSDTR
627	cmp	REJBYTE_EXT,MSG_WDTR	je p_mesginWDTR
628	jmp	rej_mesgin
629
630p_mesginWDTR:
631	cmp	ARG_1,2		jne rej_mesgin	/* extended mesg length=2 */
632	mvi	ARG_1		call inb_next	/* Width of bus */
633	mvi	INTSTAT,WDTR_MSG		/* let driver know */
634	test	RETURN_1,0xff jz mesgin_done	/* Do we need to send WDTR? */
635	cmp	RETURN_1,SEND_REJ je rej_mesgin /*
636						 * Bus width was too large 
637						 * Reject it.
638						 */
639
640/* We didn't initiate the wide negotiation, so we must respond to the request */
641	and	RETURN_1,0x7f			/* Clear the SEND_WDTR Flag */
642	mvi	DINDEX,MSG0
643	mvi	MSG0	call mk_wdtr		/* build WDTR message */
644	or	SCSISIGO,ATNO			/* turn on ATNO */
645	jmp	mesgin_done
646
647p_mesginSDTR:
648	cmp	ARG_1,3		jne rej_mesgin	/* extended mesg length=3 */
649	mvi	ARG_1		call inb_next	/* xfer period */
650	mvi	A		call inb_next	/* REQ/ACK offset */
651	mvi	INTSTAT,SDTR_MSG		/* call driver to convert */
652
653	test	RETURN_1,0xff	jz mesgin_done  /* Do we need to mk_sdtr/rej */
654	cmp	RETURN_1,SEND_REJ je rej_mesgin /*
655						 * Requested SDTR too small
656						 * Reject it.
657						 */
658	clr	ARG_1				/* Use the scratch ram rate */
659	mvi	DINDEX, MSG0
660	mvi     MSG0     call mk_sdtr
661	or	SCSISIGO,ATNO			/* turn on ATNO */
662	jmp	mesgin_done
663
664/*
665 * Is it a disconnect message?  Set a flag in the SCB to remind us
666 * and await the bus going free.
667 */
668mesgin_disconnect:
669	or	SCB_CONTROL,DISCONNECTED
670	test	FLAGS, PAGESCBS jz mesgin_done
671/*
672 * Link this SCB into the DISCONNECTED list.  This list holds the
673 * candidates for paging out an SCB if one is needed for a new command.
674 * Modifying the disconnected list is a critical(pause dissabled) section.
675 */
676	mvi	SCB_PREV, SCB_LIST_NULL
677	mvi	SEQCTL,0x50			/* PAUSEDIS|FASTMODE */
678	mov	SCB_NEXT, DISCONNECTED_SCBH
679	mov	DISCONNECTED_SCBH, SCBPTR
680	cmp	SCB_NEXT,SCB_LIST_NULL je linkdone
681	mov	SCBPTR,SCB_NEXT
682	mov	SCB_PREV,DISCONNECTED_SCBH
683	mov	SCBPTR,DISCONNECTED_SCBH
684linkdone:
685	mvi	SEQCTL,0x10			/* !PAUSEDIS|FASTMODE */
686	jmp	mesgin_done
687
688/*
689 * Save data pointers message?  Copy working values into the SCB,
690 * usually in preparation for a disconnect.
691 */
692mesgin_sdptrs:
693	call	sg_ram2scb
694	jmp	mesgin_done
695
696/*
697 * Restore pointers message?  Data pointers are recopied from the
698 * SCB anytime we enter a data phase for the first time, so all
699 * we need to do is clear the DPHASE flag and let the data phase
700 * code do the rest.
701 */
702mesgin_rdptrs:
703	and	FLAGS,0xef			/*
704						 * !DPHASE we'll reload them
705						 * the next time through
706						 */
707	jmp	mesgin_done
708
709/*
710 * Identify message?  For a reconnecting target, this tells us the lun
711 * that the reconnection is for - find the correct SCB and switch to it,
712 * clearing the "disconnected" bit so we don't "find" it by accident later.
713 */
714mesgin_identify:
715	test	A,0x78	jnz rej_mesgin	/*!DiscPriv|!LUNTAR|!Reserved*/
716
717	and	A,0x07			/* lun in lower three bits */
718	or      SAVED_TCL,A,SELID          
719	and     SAVED_TCL,0xf7
720	and     A,SELBUSB,SBLKCTL	/* B Channel?? */
721	or      SAVED_TCL,A
722	call	inb_last		/* ACK */
723
724/*
725 * Here we "snoop" the bus looking for a SIMPLE QUEUE TAG message.
726 * If we get one, we use the tag returned to switch to find the proper
727 * SCB.  With SCB paging, this requires using findSCB for both tagged
728 * and non-tagged transactions since the SCB may exist in any slot.
729 * If we're not using SCB paging, we can use the tag as the direct
730 * index to the SCB.
731 */
732	mvi	ARG_1,SCB_LIST_NULL	/* Default to no-tag */
733snoop_tag_loop:
734	test	SSTAT1,BUSFREE	jnz use_findSCB
735	test	SSTAT1,REQINIT	jz snoop_tag_loop
736	test	SSTAT1,PHASEMIS	jnz use_findSCB
737	mvi	A		call inb_first
738	cmp	A,MSG_SIMPLE_TAG jne use_findSCB
739get_tag:
740	mvi	ARG_1	call inb_next	/* tag value */
741/*
742 * See if the tag is in range.  The tag is < SCBCOUNT if we add
743 * the complement of SCBCOUNT to the incomming tag and there is
744 * no carry.
745 */
746	mov	A,COMP_SCBCOUNT	
747	add	SINDEX,A,ARG_1
748	jc	abort_tag
749
750/*
751 * Ensure that the SCB the tag points to is for an SCB transaction
752 * to the reconnecting target.
753 */
754	test	FLAGS, PAGESCBS	jz index_by_tag
755	call	inb_last			/* Ack Tag */
756use_findSCB:
757	mov	ALLZEROS	call findSCB	  /* Have to search */
758setup_SCB:
759	and	SCB_CONTROL,0xfb	  /* clear disconnect bit in SCB */
760	or	FLAGS,IDENTIFY_SEEN	  /* make note of IDENTIFY */
761	jmp	ITloop
762index_by_tag:
763	mov	SCBPTR,ARG_1
764	mov	A,SAVED_TCL
765	cmp	SCB_TCL,A		jne abort_tag
766	test	SCB_CONTROL,TAG_ENB	jz  abort_tag
767	call	inb_last			/* Ack Successful tag */
768	jmp	setup_SCB
769
770abort_tag:
771	or	SCSISIGO,ATNO			/* turn on ATNO */
772	mvi	INTSTAT,ABORT_TAG 		/* let driver know */
773	mvi	MSG_ABORT_TAG	call mk_mesg	/* ABORT TAG message */
774	jmp	mesgin_done
775
776/*
777 * Message reject?  Let the kernel driver handle this.  If we have an 
778 * outstanding WDTR or SDTR negotiation, assume that it's a response from 
779 * the target selecting 8bit or asynchronous transfer, otherwise just ignore 
780 * it since we have no clue what it pertains to.
781 */
782mesgin_reject:
783	mvi	INTSTAT, REJECT_MSG
784	jmp	mesgin_done
785
786/*
787 * [ ADD MORE MESSAGE HANDLING HERE ]
788 */
789
790/*
791 * Bus free phase.  It might be useful to interrupt the device
792 * driver if we aren't expecting this.  For now, make sure that
793 * ATN isn't being asserted and look for a new command.
794 */
795p_busfree:
796	mvi	CLRSINT1,CLRATNO
797	clr	LASTPHASE
798
799/*
800 * if this is an immediate command, perform a psuedo command complete to
801 * notify the driver.
802 */
803	test	SCB_CMDLEN,0xff	jz status_ok
804	jmp	start
805
806/*
807 * Locking the driver out, build a one-byte message passed in SINDEX
808 * if there is no active message already.  SINDEX is returned intact.
809 */
810mk_mesg:
811	mvi	SEQCTL,0x50			/* PAUSEDIS|FASTMODE */
812	test	MSG_LEN,0xff	jz mk_mesg1	/* Should always succeed */
813	
814	/*
815	 * Hmmm.  For some reason the mesg buffer is in use.
816	 * Tell the driver.  It should look at SINDEX to find
817	 * out what we wanted to use the buffer for and resolve
818	 * the conflict.
819	 */
820	mvi	SEQCTL,0x10			/* !PAUSEDIS|FASTMODE */
821	mvi	INTSTAT,MSG_BUFFER_BUSY
822
823mk_mesg1:
824	mvi	MSG_LEN,1		/* length = 1 */
825	mov	MSG0,SINDEX		/* 1-byte message */
826	mvi	SEQCTL,0x10	ret	/* !PAUSEDIS|FASTMODE */
827
828/*
829 * Functions to read data in Automatic PIO mode.
830 *
831 * According to Adaptec's documentation, an ACK is not sent on input from
832 * the target until SCSIDATL is read from.  So we wait until SCSIDATL is
833 * latched (the usual way), then read the data byte directly off the bus
834 * using SCSIBUSL.  When we have pulled the ATN line, or we just want to
835 * acknowledge the byte, then we do a dummy read from SCISDATL.  The SCSI
836 * spec guarantees that the target will hold the data byte on the bus until
837 * we send our ACK.
838 *
839 * The assumption here is that these are called in a particular sequence,
840 * and that REQ is already set when inb_first is called.  inb_{first,next}
841 * use the same calling convention as inb.
842 */
843
844inb_next:
845	or	CLRSINT0, CLRSPIORDY
846	mov	NONE,SCSIDATL			/*dummy read from latch to ACK*/
847inb_next_wait:
848	test	SSTAT1,PHASEMIS	jnz mesgin_phasemis
849	test	SSTAT0,SPIORDY	jz inb_next_wait /* wait for next byte */
850inb_first:
851	mov	DINDEX,SINDEX
852	mov	DINDIR,SCSIBUSL	ret		/*read byte directly from bus*/
853inb_last:
854	mov	NONE,SCSIDATL ret		/*dummy read from latch to ACK*/
855
856mesgin_phasemis:
857/*
858 * We expected to receive another byte, but the target changed phase
859 */
860	mvi	INTSTAT, MSGIN_PHASEMIS
861	jmp	ITloop
862
863/*
864 * DMA data transfer.  HADDR and HCNT must be loaded first, and
865 * SINDEX should contain the value to load DFCNTRL with - 0x3d for
866 * host->scsi, or 0x39 for scsi->host.  The SCSI channel is cleared
867 * during initialization.
868 */
869dma:
870	mov	DFCNTRL,SINDEX
871dma1:
872	test	SSTAT0,DMADONE	jnz dma3
873	test	SSTAT1,PHASEMIS	jz dma1		/* ie. underrun */
874
875/*
876 * We will be "done" DMAing when the transfer count goes to zero, or
877 * the target changes the phase (in light of this, it makes sense that
878 * the DMA circuitry doesn't ACK when PHASEMIS is active).  If we are
879 * doing a SCSI->Host transfer, the data FIFO should be flushed auto-
880 * magically on STCNT=0 or a phase change, so just wait for FIFO empty
881 * status.
882 */
883dma3:
884	test	SINDEX,DIRECTION	jnz dma5
885dma4:
886	test	DFSTATUS,FIFOEMP	jz dma4
887
888/*
889 * Now shut the DMA enables off and make sure that the DMA enables are 
890 * actually off first lest we get an ILLSADDR.
891 */
892dma5:
893	/* disable DMA, but maintain WIDEODD */
894	and	DFCNTRL,WIDEODD
895dma6:
896	test	DFCNTRL,0x38	jnz dma6  /* SCSIENACK|SDMAENACK|HDMAENACK */
897
898	ret
899
900/*
901 * Common SCSI initialization for selection and reselection.  Expects
902 * the target SCSI ID to be in the upper four bits of SINDEX, and A's
903 * contents are stomped on return.
904 */
905initialize_scsiid:
906	and	SINDEX,0xf0		/* Get target ID */
907	and	A,0x0f,SCSIID
908	or	SINDEX,A
909	mov	SCSIID,SINDEX ret
910
911/*
912 * Assert that if we've been reselected, then we've seen an IDENTIFY
913 * message.
914 */
915assert:
916	test	FLAGS,RESELECTED	jz return	/* reselected? */
917	test	FLAGS,IDENTIFY_SEEN	jnz return	/* seen IDENTIFY? */
918
919	mvi	INTSTAT,NO_IDENT 	ret	/* no - cause a kernel panic */
920
921/*
922 * Locate the SCB matching the target ID/channel/lun in SAVED_TCL, and the tag
923 * value in ARG_1.  If ARG_1 == SCB_LIST_NULL, we're looking for a non-tagged
924 * SCB.  Have the kernel print a warning message if it can't be found, and
925 * generate an ABORT/ABORT_TAG message to the target.  SINDEX should be
926 * cleared on call.
927 */
928findSCB:
929	mov	A,SAVED_TCL
930	mov	SCBPTR,SINDEX			/* switch to next SCB */
931	mvi	SEQCTL,0x50			/* PAUSEDIS|FASTMODE */
932	cmp	SCB_TCL,A	jne findSCB1 /* target ID/channel/lun match? */
933	test	SCB_CONTROL,DISCONNECTED jz findSCB1 /*should be disconnected*/
934	test	SCB_CONTROL,TAG_ENB jnz findTaggedSCB
935	cmp	ARG_1,SCB_LIST_NULL je foundSCB
936	jmp	findSCB1
937findTaggedSCB:
938	mov	A, ARG_1			/* Tag passed in ARG_1 */
939	cmp	SCB_TAG,A	jne findSCB1	/* Found it? */
940foundSCB:
941	test	FLAGS,PAGESCBS	jz foundSCB_ret
942/* Remove this SCB from the disconnection list */
943	cmp	SCB_NEXT,SCB_LIST_NULL je unlink_prev
944	mov	SAVED_LINKPTR, SCB_PREV
945	mov	SCBPTR, SCB_NEXT
946	mov	SCB_PREV, SAVED_LINKPTR
947	mov	SCBPTR, SINDEX
948unlink_prev:
949	cmp	SCB_PREV,SCB_LIST_NULL	je rHead/* At the head of the list */
950	mov	SAVED_LINKPTR, SCB_NEXT
951	mov	SCBPTR, SCB_PREV
952	mov	SCB_NEXT, SAVED_LINKPTR
953	mov	SCBPTR, SINDEX
954	mvi	SEQCTL,0x10	ret		/* !PAUSEDIS|FASTMODE */
955rHead:
956	mov	DISCONNECTED_SCBH,SCB_NEXT
957foundSCB_ret:
958	mvi	SEQCTL,0x10	ret		/* !PAUSEDIS|FASTMODE */
959
960findSCB1:
961	mvi	SEQCTL,0x10			/* !PAUSEDIS|FASTMODE */
962	inc	SINDEX
963	mov	A,SCBCOUNT
964	cmp	SINDEX,A	jne findSCB
965
966	mvi	INTSTAT,NO_MATCH		/* not found - signal kernel */
967	cmp	RETURN_1,SCB_PAGEDIN je return
968	or	SCSISIGO,ATNO			/* assert ATNO */
969	cmp	ARG_1,SCB_LIST_NULL jne find_abort_tag
970	mvi	MSG_ABORT	call mk_mesg
971	jmp	ITloop
972find_abort_tag:
973	mvi	MSG_ABORT_TAG	call mk_mesg
974	jmp	ITloop
975
976/*
977 * Make a working copy of the scatter-gather parameters from the SCB.
978 */
979sg_scb2ram:
980	mov	HADDR0, SCB_DATAPTR0
981	mov	HADDR1, SCB_DATAPTR1
982	mov	HADDR2, SCB_DATAPTR2
983	mov	HADDR3, SCB_DATAPTR3
984	mov	HCNT0, SCB_DATACNT0
985	mov	HCNT1, SCB_DATACNT1
986	mov	HCNT2, SCB_DATACNT2
987
988	mov	STCNT0, HCNT0
989	mov	STCNT1, HCNT1
990	mov	STCNT2, HCNT2
991
992	mov	SG_COUNT,SCB_SGCOUNT
993
994	mov	SG_NEXT0, SCB_SGPTR0
995	mov	SG_NEXT1, SCB_SGPTR1
996	mov	SG_NEXT2, SCB_SGPTR2
997	mov	SG_NEXT3, SCB_SGPTR3 ret
998
999/*
1000 * Copying RAM values back to SCB, for Save Data Pointers message, but
1001 * only if we've actually been into a data phase to change them.  This
1002 * protects against bogus data in scratch ram and the residual counts
1003 * since they are only initialized when we go into data_in or data_out.
1004 */
1005sg_ram2scb:
1006	test	FLAGS, DPHASE	jz return
1007	mov	SCB_SGCOUNT,SG_COUNT
1008
1009	mov	SCB_SGPTR0,SG_NEXT0
1010	mov	SCB_SGPTR1,SG_NEXT1
1011	mov	SCB_SGPTR2,SG_NEXT2
1012	mov	SCB_SGPTR3,SG_NEXT3
1013	
1014	mov	SCB_DATAPTR0,SHADDR0
1015	mov	SCB_DATAPTR1,SHADDR1
1016	mov	SCB_DATAPTR2,SHADDR2
1017	mov	SCB_DATAPTR3,SHADDR3
1018
1019/*
1020 * Use the residual number since STCNT is corrupted by any message transfer
1021 */
1022	mov	SCB_DATACNT0,SCB_RESID_DCNT0
1023	mov	SCB_DATACNT1,SCB_RESID_DCNT1
1024	mov	SCB_DATACNT2,SCB_RESID_DCNT2 ret
1025
1026/*
1027 * Add the array base TARG_SCRATCH to the target offset (the target address
1028 * is in SCSIID), and return the result in SINDEX.  The accumulator
1029 * contains the 3->8 decoding of the target ID on return.
1030 */
1031ndx_dtr:
1032	shr	A,SCSIID,4
1033	test	SBLKCTL,SELBUSB	jz ndx_dtr_2
1034	or	A,0x08		/* Channel B entries add 8 */
1035ndx_dtr_2:
1036	add	SINDEX,TARG_SCRATCH,A ret
1037
1038/*
1039 * If we need to negotiate transfer parameters, build the WDTR or SDTR message
1040 * starting at the address passed in SINDEX.  DINDEX is modified on return.
1041 * The SCSI-II spec requires that Wide negotiation occur first and you can
1042 * only negotiat one or the other at a time otherwise in the event of a message
1043 * reject, you wouldn't be able to tell which message was the culpret.
1044 */
1045mk_dtr:
1046	test	SCB_CONTROL,NEEDWDTR jnz  mk_wdtr_16bit
1047	mvi	ARG_1, MAXOFFSET	/* Force an offset of 15 or 8 if WIDE */
1048
1049mk_sdtr:
1050	mvi	DINDIR,1		/* extended message */
1051	mvi	DINDIR,3		/* extended message length = 3 */
1052	mvi	DINDIR,1		/* SDTR code */
1053	call	sdtr_to_rate
1054	mov	DINDIR,RETURN_1		/* REQ/ACK transfer period */
1055	cmp	ARG_1, MAXOFFSET je mk_sdtr_max_offset
1056	and	DINDIR,0x0f,SINDIR	/* Sync Offset */
1057
1058mk_sdtr_done:
1059	add	MSG_LEN,COMP_MSG0,DINDEX ret	/* update message length */
1060
1061mk_sdtr_max_offset:
1062/*
1063 * We're initiating sync negotiation, so request the max offset we can (15 or 8)
1064 */
1065	/* Talking to a WIDE device? */
1066	test	SCSIRATE, WIDEXFER	jnz wmax_offset	
1067	mvi	DINDIR, MAX_OFFSET_8BIT
1068	jmp	mk_sdtr_done
1069
1070wmax_offset:
1071	mvi	DINDIR, MAX_OFFSET_16BIT
1072	jmp	mk_sdtr_done
1073
1074mk_wdtr_16bit:
1075	mvi	ARG_1,BUS_16_BIT
1076mk_wdtr:
1077	mvi	DINDIR,1		/* extended message */
1078	mvi	DINDIR,2		/* extended message length = 2 */
1079	mvi	DINDIR,3		/* WDTR code */
1080	mov	DINDIR,ARG_1		/* bus width */
1081
1082	add	MSG_LEN,COMP_MSG0,DINDEX ret	/* update message length */
1083	
1084sdtr_to_rate:
1085	call	ndx_dtr			/* index scratch space for target */
1086	shr	A,SINDIR,0x4
1087	dec	SINDEX			/* Preserve SINDEX */
1088	and	A,0x7
1089	clr	RETURN_1
1090sdtr_to_rate_loop:
1091	test	A,0x0f	jz sdtr_to_rate_done
1092	add	RETURN_1,0x19
1093	dec	A	
1094	jmp	sdtr_to_rate_loop
1095sdtr_to_rate_done:
1096	shr	RETURN_1,0x2
1097	add	RETURN_1,0x19
1098	test	SXFRCTL0,ULTRAEN jz return
1099	shr	RETURN_1,0x1
1100return:
1101	ret
1102