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