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