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