sys7.1-doc-wip/OS/SCSIMgr4pt3/HALc96BIOS.a
2019-07-27 22:37:48 +08:00

1248 lines
42 KiB
Plaintext

;
; File: HALc96BIOS.a
;
; Contains: Fast Data XFer routines for BIOS/53c96 machines
;
; Written by: Clinton Bauder
;
; Copyright: © 1990-1994 by Apple Computer, Inc., all rights reserved.
;
; Change History (most recent first):
;
; <SM20> 1/25/94 DCB Got rid of a bogus extra line in the bus error handler
; installer.
; <SM18> 12/23/93 DCB Adding code to save the handshake values between calls to the
; fast read and write routines. This means scatter gather list
; elements don't have to be multiples of the smallest hanshake
; size.
; <SM17> 12/9/93 DCB FastWrite left the bus error handler installed after it had
; finished.
; <SM16> 11/22/93 DCB Somehow I left a totally bogus bne in the code I added last time
; This totally hosed the Bus Error Handler in the write case.
; <SM15> 11/17/93 DCB Fixing the bus error handling so that we don't step on the TIB
; interpreter's globals when we remember what the data direction
; is.
; <SM14> 10/29/93 DCB Adding calls to deferAndWait after calls to Wt4SCSI do reduce
; the interrupt level during transfers. Also added code to remove
; the Bus Error handler when we go asychronous so that we wouldn't
; end up chaining to our own BEH.
; <SM13> 10/14/93 pdw <MC3><MC2>
; <MC3> 10/12/93 pdw Added support for Synchronous data transfers, rewrote State
; Machine, message handling etc.
; <MC2> 9/26/93 pdw Rolled in Clinton's changes.
; <SM12> 9/27/93 DCB Grrr, I missed a tst.w d0 in FastWrite96Bios which I should have
; changed to a tst.w d1.
; <SM11> 9/25/93 DCB The scHandshake interpreter wasn't checking d1 after each
; iteration of FastRead_inner. I was also stepping on A0 when I
; removed the BusError Handler at the end of a data transaction.
; This was playing havoc with the Handshake intepreter because it
; was using the SCSIGlobals as a Handshake ptr.
; <SM10> 9/16/93 DCB Fixing the busError handler to resolve a conflict between two
; definitions of yeOldeBusErrorVect. Also changed the handshake
; interpreter to fix a residual length discrepancy.
; <SM9> 9/9/93 pdw Lots of little changes. Name changes, temporary cache_bug
; stuff.
; <SM8> 8/19/93 DCB Improving the bus error handler so that disconnects at
; non-polled bytes will work properly.
; <SM7> 8/13/93 pdw Trivial little IMPORT changes and stuff.
; <SM6> 7/17/93 pdw Lots of little things (involving interrupt checking and
; currentPhase).
; <SM5> 6/29/93 pdw Massive checkins: Change asynchronicity mechanism to CallMachine
; stack switching mechanism. Adding support for Cold Fusion.
; Rearranging HW/SW Init code. Some code optimizations.
; <SM4> 5/25/93 DCB SCSI Globals are now included in XPTEqu.a
; <SM3> 5/5/93 PW Converted names to meanies-friendly names. Updated with latest
; from Ludwig stuff.
; <SM2> 4/8/93 joe Added EXPORTs for OneByteRead_BIOS and OneByteWrite_BIOS. The
; lack of those exports was breaking the build.
; <1> 4/8/93 DCB first checked in
;
;==========================================================================
MACHINE MC68020 ; '020-level
BLANKS ON ; assembler accepts spaces & tabs in operand field
PRINT OFF ; do not send subsequent lines to the listing file
; don't print includes
PostNOP EQU 1 ;
INCLUDE 'SysErr.a'
INCLUDE 'SysEqu.a'
INCLUDE 'HardwarePrivateEqu.a'
INCLUDE 'MC680x0.a'
INCLUDE 'Debug.a' ; for NAME macro
INCLUDE 'ACAM.a'
INCLUDE 'SCSI.a'
INCLUDE 'XPTEqu.a'
INCLUDE 'SCSIEqu53c96.a'
INCLUDE 'SIMCoreEqu.a'
INCLUDE 'HALc96equ.a'
PRINT ON ; do send subsequent lines to the listing files
CASE OBJECT
HALc96DataBIOS PROC EXPORT
IMPORT Wt4SCSIInt, Ck4SCSIInt
IMPORT Ck4DREQ
IMPORT WtForFIFOData
IMPORT RecordEvent
IMPORT Wt4PhaseStable
IMPORT DeferAndWait
EXPORT FastRead_96_BIOS,FastWrite_96_BIOS
EXPORT OneByteRead_BIOS
EXPORT OneByteWrite_BIOS
WITH HALc96GlobalRecord
WITH SIM_IO, HALactions, SCSIGlobalsRec, SCSIPhase
;--------------------------------------------------------------------------
; OneByteRead_BIOS/OneByteWrite_BIOS - proc to transfer 1 byte
;
; d0 - <-- error (if any)
; d1 - --> copy of d2
; d1 - <-- bytes transferred
; d2 - --> number of bytes to transfer
; d3 - scratch - saved
; d4 - --> type of transfer to perform
; d5 - scratch - saved
; d6 - scratch - saved
;
; a0 - scratch - saved
; a1 - SCSI chip read base address - NON-SERIALIZED
; a2 - ptr to data buffer - saved
; a3 - SCSI chip read base address - SERIALIZED
; A4 - ptr to HAL Action PB
; a5 - ptr to HAL Globals
OneByteRead_BIOS ;
RecCmd $10, 'B',$01
bra.s @oneReadBot ;
@oneReadTop
move.b #cIOXfer, rCMD(a3) ; load IO transfer cmd & begin xfers
eieio
bsr.w Wt4SCSIInt ; Wait for interrupt
move.b rFIFO(a3), (a2)+ ; xfer byte from FIFO into input buffer
@oneReadBot
cmp.b #kDataInPhase, currentPhase(A5)
dbne d2,@oneReadTop ;
bne.s @wrongPhase
moveq.l #0, D2 ; fell through db - we did all of it
@wrongPhase ; fell through ne - we have the real count
move.l d2,d1 ; remember how much we did
rts
NAME 'OneByteRead_BIOS'
OneByteWrite_BIOS
bra.s @oneWriteBot ;
@oneWriteTop
move.b (a2)+, rFIFO(a3) ; preload the FIFO
@oneWriteBot
dbra d2,@oneWriteTop ;
RecCmd $10, 'B',$02
move.b #cIOXfer, rCMD(a3) ; load IO transfer cmd & begin xfers
eieio
bsr.w Wt4SCSIInt ; Wait for interrupt
move.b rFIFOflags(a3), d1 ; get FIFO status - how many bytes in FIFO
and.w #mFIFOCount, d1 ; this is the number we didn't xfer
rts
NAME 'OneByteWrite_BIOS'
;————————————————————————————————————————————————————————————————————————————
; FastRead_96_BIOS - implements FastRead
;
; Called by: Transfer
;
; All primitive data transfer routines assume:
;
; Inputs --->
; -> D2.L number of bytes to transfer
; -> D1.L copy of d2
; -> A2 ptr to data buffer - saved
; -> A3 SCSI chip read base address - SERIALIZED
; -> A5 ptr to SCSI Mgr globals
;
; Outputs <---
; <- d0.W error (if any)
; <- d1.L bytes not transferred
;
; Internal ---
; D3 - trashed
; A0 - scratch - saved
; A1 - SCSI chip read base address - NON-SERIALIZED
; A2 - ptr to data buffer - saved
; A3 - SCSI chip read base address - SERIALIZED
; A5 - ptr to SCSI Mgr globals
;
; Method of Data Transfer: (uses Pseudo-DMA)
; 0) Make sure we got our intrp from the last cmd send
; 1) Parcel transfer into 64KB blocks since TC regr. handles 64KB max
; 2) Read 1st byte if input buffer is NOT word aligned
; 3) Calc. the number of 32-byte block transfers to perform
; 4) Calc. the remaining number of byte transfers to perform
; 5) Read data 32-byte blocks at a time using word MOVEs
; 6) Read remaining data a word at a time
; 7) Transfer residual byte if there is one
D2_thisTime EQU D2 ; .l = number of bytes remaining in this block
D3_total EQU D3 ; .l = number of bytes remaining in this request
FastRead_96_BIOS
;
; Loop thru scsiHandshake structure
;
move.l D2, D3_total ; save original total request count
@firstHandshake
lea scsiHandshake(A0), A1 ; and now with ptr to scsiHandshake
tst.w (A1) ; if no handshake,
beq.s FastReadBIOS_inner ; -> skip handshake, goto inner routine
moveq #0, D2_thisTime
move.w hdshkRemainder(a0), D2_thisTime ; Leftover Hansdhake?
beq.b @next ; nope, start handshake over again
move.w #0, hdshkRemainder(a0) ; don't try to do it again...
moveq #0, d0
move.b hdshkIndex(a0), d0 ; find out which handshake element we were working on
lsl.w #1, d0 ; adjust for word length
add.w d0, A1 ; index into the handshake array
bra.b @handshake ; and do it
@next
moveq.l #0, D2_thisTime
move.w (A1)+, D2_thisTime
beq.s @firstHandshake
@handshake
sub.l D2_thisTime, D3_total ; decrement total by this hsk count
beq.s @lastOne ; if same, -> this is the last one
blo.s @useTotal ; if total<hsk, -> use the total left
move.l A1, -(sp)
bsr.s FastReadBIOS_inner ; else, use the hsk value as count
move.l (sp)+, A1
tst.w D1 ; did we go out of phase?
bne.s @didntFinish ; -> yes, adjust unxferred count and ret
bra.s @next ; -> no, get the next hsk for next xfer
@didntFinish
add.l D3_total, D1 ; readjust total count by unxfered amount
rts ; (D1 is return value)
@useTotal
add.l D2_thisTime, D3_total ; restore total to what it was...
move.l D2_thisTime, D0 ; remember what handshake was
sub.l D3_total, D0 ; and figure out the remainder was
move.w D0, hdshkRemainder(A0) ; so we can remember it for later
move.l A1, D0 ; get next hanshake
sub.l #2, D0 ; and back up one word (element)
lea scsiHandshake(A0), A1 ; get the first hanshake
sub.l A1, D0 ; calculate the offset
move.b D0, hdshkIndex(A0) ; and remember it for later (whew!)
move.l D3_total, D2_thisTime
@lastOne
bsr.s FastReadBIOS_inner
rts
;————————————
FastReadBIOS_inner
IF 1 AND RECORD_ON THEN
pea 'FsRd' ; EVENT =
move.l D2, -(sp) ; number of bytes
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l pdmaAddr(A5), a1 ; put serialized version back in
moveq.l #iPhaseMsk, d0 ; load mask for phase bits
and.b rSTA(a3), d0 ; are we in data-in phase?
cmpi.b #iDataIn, d0 ; data-in phase bits = 001
bne.w PhaseErrAtStart ; bra. on phase err
cmpi.l #3, d2 ; if not 3 or less bytes read then...
bhi.s @moreThan3 ; jump into move.l loop
@doSingles
bsr OneByteRead_BIOS ;
bra @exit
@moreThan3
move.l a2,d6 ; get location of buffer
and.l #3,d6 ; odd words or bytes mean alignment req'd
bne.w @alignBuffer ;
@aligned
;
; Install our bus error handler because we are going into a routine that blindly accesses
; the SCSI chip (and it might not always be ready)
;
bsr.w InstallBEH_BIOS ; install our Bus Error Handler
move.l d2, d6 ; d6 = number 64KB block to perform
swap d6 ; upper word of d6 = lower word of d2
andi.l #$0000FFFF, d2 ; mask out upper word
beq @2 ; if 0 then we have $10000 (64K) bytes to xfer
bra.s @skipPhaseCk
@next64KB
moveq.l #iPhaseMsk, d0 ; load mask for phase bits
and.b rSTA(a3), d0 ; are we in data-in phase?
cmpi.b #iDataIn, d0 ; data-in phase bits = 001
bne.w @outOfPhase ; outta here.
@skipPhaseCk
move.l d2, d4 ; d4 <- d2
move.b d4, rXCL(a3) ; TC regr (least-sig. byte) <- d4.b
lsr.l #8, d4 ; get upper byte of low word
move.b d4, rXCM(a3) ; TC regr (most-sig. byte) <- d4.b
eieio
IF RECORD_ON and RECORD_rCMD THEN
pea 'rCMD' ; EVENT = Wt4S
move.w #$90, -(sp) ; command
move.w busID(A5), -(sp) ; busID
bsr RecordEvent
addq.l #8, sp
ENDIF
move.b #cDMAXfer, rCMD(a3) ; load DMA transfer cmd & begin xfers
; DREQ* should be active at this time
eieio
move.l d2, d4 ; d4 = copy of transfer count
lsr.l #7, d4 ; divide xfer count by 128
and.l #$7f,d2 ; remainder is byte count after 128 byte moves
ror.l #1, d2 ; xfer byte count to word & remember odd byte
move.l d2,d0
ror.l #1,d0 ; xfer word count to long & remember odd word
neg.w d0 ; negate to form a backward jump offset
nop ; squoosh pipeline
jmp @RdLoop(d0.w*2) ; bra. into the loop
@read128 ;
move.l (a1),(a2)+ ; read 16 bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 16 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 32 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 48 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 64 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 80 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 96 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 112 bytes
move.l (a1),(a2)+ ; read 16 more bytes
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ;
move.l (a1),(a2)+ ; finished 128 bytes
@RdLoop ;
dbra d4, @read128 ; d4 = # of 128-byte transfers
IF PostNOP THEN
nop ; squoosh pipeline
ENDIF
; INT & TC bits should be TRUE at this point
btst.l #31, d0 ; check if we have a residual word
beq.s @chkByte ; bra. if no residual
@resWord
bsr.l WtForFIFOData ; returns number of bytes in FIFO
move.w (a1),(a2)+ ; xfer residual word
@chkByte
bsr.w RemoveBEH_BIOS ; get rid of our BEH while we are async
bsr.w Wt4SCSIInt ; Wait for intrp w/o timeout
bne.s @disconnected ; bra. if ended up disconnected
jsr DeferAndWait ; defer til interupts are enabled
bsr.w InstallBEH_BIOS ; put the BEH back
btst.l #31, d2 ; check if we have a residual byte
beq.s @2 ; bra. if no residual
@resByte
bsr.l WtForFIFOData ; returns number of bytes in FIFO
move.b rFIFO(a3), (a2)+ ; xfer residual byte
@2
move.l #$10000, d2 ; init to transfer 64K bytes
dbra d6, @next64KB ;
@disconnected
;
; Remove our bus error handler
;
bsr.w RemoveBEH_BIOS ; get rid of our BEH
@goodFRead
moveq.l #0, D1 ; d1 = # of bytes transferred
moveq.l #noErr, d0 ; successful read op
@exit
rts ;
@alignBuffer
bra.s @alignLoop
@misAligned
IF RECORD_ON and RECORD_rCMD THEN
pea 'rCMD' ; EVENT = Wt4S
move.w #$10, -(sp) ; command
move.w busID(A5), -(sp) ; busID
bsr RecordEvent
addq.l #8, sp
ENDIF
move.b #cIOXfer, rCMD(a3) ; load non-DMA transfer cmd & begin 1 byte xfer
;
; WtForInt
;
@noTimeoutWait
clr.l d5 ;
move.b rSTA(a3), d5 ; = x | x | x | rSTA
bpl.s @noTimeoutWait ; ...loop until intrp req is detected
move.b D5, D0
and.b #iPhaseMsk, D0
move.b D0, currentPhase(A5)
swap d5 ; = x | rSTA | x | x
move.b rFIFOflags(a3), d5 ; = x | rSTA | x | rFOS
lsl.w #8, d5 ; = x | rSTA | rFOS | x
move.b rINT(a3), d5 ; = x | rSTA | rFOS | rINT
move.l d5, d0 ; for checking for disconnect
swap d5 ; = rFOS | rINT | x | rSTA
move.b rFIFO(a3), (a2)+ ; get the byte
subq.l #1, D2 ; decr. for DBRA
beq.s @goodFRead ; if xfer complete - done
; get Disconnect & Bus Service bits
andi.b #(1<<bDisconnected)+(1<<bBusService), d0
cmpi.b #1<<bBusService, d0 ; expecting: not disconnected
bne.s @phaseErr ; bra. if ended up disconnected
;
; Make sure that we're in DataIn phase between each byte
;
moveq.l #iPhaseMsk, d0 ; load mask for phase bits
and.b rSTA(a3), d0 ; are we in data-in phase?
move.b D0, currentPhase(A5)
cmpi.b #iDataIn, d0 ; data-in phase bits = 001
bne.s @phaseErr ; bra. on phase err
@alignLoop
dbra d6, @misAligned ; check to see if we are done aligning
bra.w @aligned ; transfer the rest of data
; ———— No alignment or done aligning ————
@doneAligning ; We went out of phase early in the process - we still have to look at d2
; also we don't have to remove the bus error handler
@phaseErr
swap d6 ; calculate bytes left to transfer
move.w d4, d6 ; get low order word (loops to go)
lsl.l #5, d6 ; multiply by 32
ext.l d2 ; make d2 a long
addq.l #1, d2 ; undo adjustment for dbra
add.l d2, d6 ; add to total
moveq.l #noErr, d0 ; assume successful read op
move.l d6, d1 ; d1 = # of bytes not transferred
beq.s @exit ; if zero, no error
moveq.l #scPhaseErr, d0 ; else return a phase error
bra.s @exit
@outOfPhase ; We went out of phase after a 64K chunk - we only need to look at d6
bsr.w RemoveBEH_BIOS ; get rid of our BEH
add.l #1,d6 ; undo for dbra
swap d6 ; d6 contains the number of 64k xfers
move.w #0, D6 ; we only care about the high word
move.l d6,d1 ; return the number of bytes left to be xferred
beq.s @exit ; if zero, no error
moveq.l #scPhaseErr, d0 ; else return a phase error
bra.s @exit
RTSNAME 'FastRead96_BIOS'
;————————————————————————————————————————————————————————————————————————————
; FastWrite - implements Blind Write
;
; Called by: Transfer
;
; All primitive data transfer routines assume:
;
; d0 - <-- error (if any)
; d1 - --> copy of d2
; d1 - <-- bytes transferred
; d2 - --> number of bytes to transfer
; d3 - scratch - saved
; d4 - --> type of transfer to perform
; d5 - scratch - saved
; d6 - scratch - saved
;
; a0 - scratch - saved
; a1 - SCSI chip read base address - NON-SERIALIZED
; a2 - ptr to data buffer - saved
; a3 - SCSI chip read base address - SERIALIZED
; A4 - ptr to HAL Action PB
; A5 - ptr to SCSI Mgr globals
; a5 - scratch - saved
;
; Method of Data Transfer: (uses pseudo-DMA mode)
; 0) Make sure we got our intrp from the last cmd send
; 1) Parcel transfer into 64KB blocks since TC regr. handles 64KB max
; 2) Preload FIFO with non-aligned byte; get us word aligned
; 3) Calc. the number of 32-byte block transfers to perform
; 4) Calc. the remaining number of transfers to perform
; 5) Write data 32-byte blocks at a time using word MOVEs
; 6) Write remaining data using word MOVEs
; 7) Transfer residual byte if there is one
;————————————
FastWrite_96_BIOS
;
; Loop thru scsiHandshake structure
;
move.l D2, D3_total ; save original total request count
@firstHandshake
lea scsiHandshake(A0), A1 ; and now with ptr to scsiHandshake
tst.w (A1) ; if no handshake,
beq.s FastWrite96BIOS_inner ; -> skip handshake, goto inner routine
moveq #0, D2_thisTime
move.w hdshkRemainder(a0), D2_thisTime ; Leftover Hansdhake?
beq.b @next ; nope, start handshake over again
move.w #0, hdshkRemainder(a0) ; don't try to do it again...
moveq #0, d0
move.b hdshkIndex(a0), d0 ; find out which handshake element we were working on
lsl.w #1, d0 ; adjust for word length
add.w d0, A1 ; index into the handshake array
bra.b @handshake ; and do it
@next
moveq.l #0, D2_thisTime
move.w (A1)+, D2_thisTime
beq.s @firstHandshake
@handshake
sub.l D2_thisTime, D3_total ; decrement total by this hsk count
beq.s @lastOne ; if same, -> this is the last one
blo.s @useTotal ; if total<hsk, -> use the total left
move.l A1, -(sp)
bsr.s FastWrite96BIOS_inner ; else, use the hsk value as count
move.l (sp)+, A1
tst.w D1 ; did we go out of phase?
bne.s @didntFinish ; -> yes, adjust unxferred count and ret
bra.s @next ; -> no, get the next hsk for next xfer
@didntFinish
add.l D3_total, D1 ; readjust total count by unxfered amount
rts ; (D1 is return value)
@useTotal
add.l D2_thisTime, D3_total ; restore total to what it was...
move.l D2_thisTime, D0 ; remember what handshake was
sub.l D3_total, D0 ; and figure out the remainder was
move.w D0, hdshkRemainder(A0) ; so we can remember it for later
move.l A1, D0 ; get next hanshake
sub.l #2, D0 ; and back up one word (element)
lea scsiHandshake(A0), A1 ; get the first hanshake
sub.l A1, D0 ; calculate the offset
move.b D0, hdshkIndex(A0) ; and remember it for later (whew!)
move.l D3_total, D2_thisTime
@lastOne
bsr.s FastWrite96BIOS_inner
rts
;————————————
FastWrite96BIOS_inner
IF 1 AND RECORD_ON THEN
pea 'FsWr' ; EVENT =
move.l D2, -(sp) ; number of bytes
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l pdmaAddr(A5), a1 ; put serialized version back in
moveq.l #iPhaseMsk, d0 ;
and.b rSTA(a3), d0 ; are we in data-out phase?
bne.w PhaseErrAtStart ; data-out phase bits = 0, bra. on phase err
cmpi.l #3, d2 ; if not 3 or less bytes write then...>
bhi.s @moreThan3 ; jump into move.l loop
@doSingles
bsr OneByteWrite_BIOS ; Actually does up to three bytes
bra @exit
@moreThan3
move.l a2,d6 ; get location of buffer
and.l #3,d6 ; odd words or bytes mean alignment req'd
bne.w @alignLoop ;
@aligned
;
; Install our bus error handler because we are going into a routine that blindly accesses
; the SCSI chip (and it might not always be ready)
;
bsr.w InstallBEH_BIOS ; install our BEH
move.l d2, d6 ; d6 = number 64KB block to perform
swap d6 ; upper word of d6 = lower word of d2
andi.l #$0000FFFF, d2 ; mask out upper word
beq @2 ; if 0 then we have $10000 (64K) bytes to xfer
bra.b @skipPhaseCk
@next64KB ; buffer is aligned from this point
moveq.l #iPhaseMsk, d0 ; load mask for phase bits
and.b rSTA(a3), d0 ; are we in data-out phase?
bne.w @phaseErr ; nope, outta here.
@skipPhaseCk
move.l d2, d4 ; d4 <- d2
move.b d4, rXCL(a3) ; TC regr (least-sig. byte) <- d4.b
lsr.l #8, d4 ; get upper byte of low word
move.b d4, rXCM(a3) ; TC regr (most-sig. byte) <- d4.b
eieio
IF RECORD_ON and RECORD_rCMD THEN
pea 'rCMD' ; EVENT = Wt4S
move.w #$90, -(sp) ; command
move.w busID(A5), -(sp) ; busID
bsr RecordEvent
addq.l #8, sp
ENDIF
move.b #cDMAXfer, rCMD(a3) ; load DMA transfer cmd & begin xfers
; DREQ* should be active at this time
eieio
move.l d2, d4 ; d4 = copy of transfer count
lsr.l #7, d4 ; divide xfer count by 128
and.l #$7f,d2 ; remainder is byte count after 128 byte moves
ror.l #1, d2 ; xfer byte count to word & remember odd byte
move.l d2,d0
ror.l #1,d0 ; xfer word count to long & remember odd word
neg.w d0 ; negate to form a backward jump offset
nop ; squoosh pipeline
jmp @WrLoop(d0.w*2) ; bra. into the loop
@write128 ;
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 16 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 32 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 48 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 64 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 80 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 96 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 112 bytes
move.l (a2)+,(a1) ; write 16 bytes
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ;
move.l (a2)+,(a1) ; finished 128 bytes
@WrLoop
dbra d4, @write128 ; d4 = # of 128-byte tranfers
eieio
btst.l #31, d0 ; check if we have a residual word
beq.s @chkByte ; bra. if no residual
@resWord
move.w (a2)+,rDMA(a3) ; xfer residual byte
eieio
@chkByte
btst.l #31, d2 ; check if we have a residual byte
beq.s @noResidual ;
@resByte
move.b (a2)+,rDMA(a3) ; xfer residual byte
eieio
@noResidual ; INT & TC maybe TRUE at this point
bsr.w RemoveBEH_BIOS ; get rid our our BEH while we are async
bsr.w Wt4SCSIInt ; Wait for int
bne.s @goodFWrite ; bra. if ended up disconnected
jsr DeferAndWait ; defer til interupts are enabled
bsr.w InstallBEH_BIOS ; put the BEH back
@2
move.l #$10000, d2 ; init to transfer 64K bytes
dbra d6, @next64KB ;
moveq.l #mFIFOCount, d2 ; <H5> thru next <H5>
and.b rFIFOflags(a3), d2 ; add un-xferred byte in FIFO
beq.s @disconnected ;
moveq.l #scPhaseErr, d0 ; return a phase error
bra.s @badFWrite ; <H5> from prev <H5>
@disconnected
;
; Remove our bus error handler
;
bsr.w RemoveBEH_BIOS ; get rid our our BEH
@goodFWrite
moveq.l #0, D1 ; d1 = # of bytes transferred
moveq.l #noErr, d0 ; successful write op
@exit
rts ;
@misAligned ;
subq.l #1, d2 ; adjust for transfer count calc
move.b (a2)+, rFIFO(a3) ; ...preload fifo with odd byte
eieio
@alignLoop
dbra d6,@misAligned ; keep doing it until we are long aligned
bra.w @aligned ; transfer the rest of data
@phaseErr
bsr.w RemoveBEH_BIOS ; get rid our our BEH
add.l #1,d6 ; undo for dbra
swap d6 ; d6 contains the number of 64k xfers
move.w #0, D6 ; we only care about the high word
move.l d6,d1 ; return the number of bytes left to be xferred
beq.s @exit ; if zero, no error
moveq.l #scPhaseErr, d0 ; else return a phase error
bra.s @exit
@badFWrite ;
IF RECORD_ON and RECORD_rCMD THEN
pea 'rCMD' ; EVENT = Wt4S
move.w #$01, -(sp) ; command
move.w busID(A5), -(sp) ; busID
bsr RecordEvent
addq.l #8, sp
ENDIF
move.b #cFlushFIFO, rCMD(a3) ; Flush FIFO
eieio
bra.s @exit
RTSNAME 'FastWrite_96_BIOS'
;————————————————————————————————————————————————————————————————————————————
PhaseErrAtStart
move.l D2, D1 ; return same number as requested
moveq.l #scPhaseErr, d0 ; return a phase error
rts ;
NAME 'PhaseErrAtStart'
InstallBEH_BIOS
move.l a0,-(sp) ; save a0 for scsiHandshake stuff
move.l SCSIGlobals, A0 ; scsiGlobals
move.l BusErrVct, yeOldeBusErrVct(A0) ; save previous Bus Error vector
lea BusErrHandler_96_BIOS, A0 ; get address of our BEH
move.l A0, BusErrVct ; put ours in there
move.l (sp)+,a0 ; restore a0
rts
RTSNAME 'InstallBEH_BIOS'
RemoveBEH_BIOS
move.l ([SCSIGlobals],yeOldeBusErrVct), BusErrVct ; restore previous Bus Error vector
rts
RTSNAME 'RemoveBEH_BIOS'
;___________________________________________________________________________
;
; BusErrHandler_96
; When the SCSI Mgr is performing a blind data transfer, it patches
; out the bus error vector. The old SCSI Mgr bus error handler
; assumed that if it got called, it must be handling a SCSI bus error.
; Unfortunately, NuBus cards could bus error while the SCSI Mgr is
; installed. To be a better bus error citizen, the SCSI bus error
; handler now checks that the fault address is the SCSI chip, and if
; not, it chains to the bus error handler that it replaced.
;
; This code returns control to Transfer_96 and not to the routine which
; caused the bus error. It does this by popping off the buserr stack
; frame and then doing an RTS, so...
; DON'T PUT ANYTHING ON THE STACK IN TRANSFER ROUTINES (FastRead,
; Fast…, etc.). At least don't leave it there during periods where a
; buserr may be possible.
;
___________________________________________________________________________;
WITH AEXFrame,SCSIGlobalsRec ;XferFrame
savedRegs REG d0-d3/a0-a3/a5 ; save these registers because we need to use them
savedRSize EQU 9*4 ; # bytes on stack for saved registers
BusErrHandler_96_BIOS
; Is it our fault? -----
subq.l #4, sp ; make room for return addr (@notSCSIFault)
movem.l savedRegs, -(sp) ;
lea savedRSize+4(sp), a0 ; make A0 our AEXFrame pointer (regs+1 LW on stack)
;
; XPT should install its BusErrHandler and pass a ptr to the AEXFrame and the SIMg down into
; the SIM for every one of the SIMs that have registered a BEH. The SIM must then pass the
; HALg down here. (But we'll cheat for now since only our buses will need this BEH).
move.l SCSIGlobals, A1
cmp.l berr_halg0(A1),A5 ; are we talking to our bus 0?
bne.s @notSCSIFault
move.l baseRegAddr(a5),a3 ; get the base address of the c96
move.l pdmaAddr(A5),d0 ; get the pseudo DMA Address
cmp.l FaultAddr(A0),d0 ; compare with faulted address
beq.s @SCSIFault ; if so, start processing the bus error
lea BIOSAddr,a1 ; setup for testing BIOS buffer
btst.b #bBIOSSCSIBERR,BIOS_PDMA(a1) ; did we buserr on access via BIOS ?
bne.s @SCSIFault ; if so, start processing the bus error
; It's not our fault ------
@notSCSIFault
move.l SCSIGlobals, A1 ; Get the SCSI globals again
move.l yeOldeBusErrVct(A1), savedRSize(sp) ; stuff old Bus Error vector
movem.l (sp)+, savedRegs ; restore regs
rts ; jump to old handler, assuming it'll RTE
NAME 'BusErrHandlerTOP_BIOS'
; It's all our fault (blame it on us) ------
@SCSIFault
move.w sr, savedSR(a5) ; save sr
ori.w #$0700, sr ; \/ \/ \/ Block Ints \/ \/ \/
; Wait for either DREQ or INT
IF RECORD_ON THEN
pea 'Berr' ;
move.l xPC(a0),-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l HALactionPB.ioPtr(A4),a1 ; get the IOPB
move.l scsiFlags(A1), D0
and.l #scsiDirectionMask, D0 ; are we data in or out?
cmp.l #scsiDirectionIn, D0 ; We may not want to do writebacks if we are
; writing.
bne.w @notDataIn
@DataIn ;****************************************
; clean up the writebacks on the stack frame
move.w WB1S(A0), d0 ; check WB1 for validity
move.l WB1A(A0), A1 ; pass WB Address
move.l WB1D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
move.w WB2S(A0), d0 ; check WB2 for validity
move.l WB2A(A0), A1 ; pass WB Address
move.l WB2D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
move.w WB3S(A0), d0 ; check WB3 for validity
move.l WB3A(A0), A1 ; pass WB Address
move.l WB3D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
@wtloop
movem.l D1-D2/A0, -(sp)
bsr Ck4DREQ ;
movem.l (sp)+, D1-D2/A0
bne.s @ckBIOS
movem.l D1-D2/A0, -(sp)
bsr Ck4SCSIInt ; see if we have a phase change or something
movem.l (sp)+, D1-D2/A0
bne.w @phzChange ;
bra.b @wtloop
@ckBIOS
IF RECORD_ON THEN
pea 'BERD' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
; READ case for BIOS *********************************
; we have to check the residual register in BIOS....
; 1. if there is a residual word we have to retrieve it, read another word
; with the posted DREQ and nuke the stack to skip the move.l that buserr'd
; 2. if there is no residual then we can just rte like flint!
;
lea BIOSAddr,a1 ; setup for testing BIOS buffer
btst.b #bBIOSR1Cmplt,BIOS_PDMA(a1) ; is there a residual word?
beq.w @doRTE ; 0=no, so restart move.l
;
; Only 1 word of the long word read made it from the controller. We have to
; move the word stored in the residual buffer within BIOS to memory and then
; manually extract the next word from the controller.
; Note: the value of a2 will be the value before the move.l postincrement.
; We also have to advance the PC so that the rte doesn't restart the faulted
; instruction.
move.w BIOS_SCSI_RESID(a1),(a2)+ ; retrieve the residual word stored in BIOS
move.w rDMA(a3),(a2)+ ; get word from chip and put into user's buffer <H4>
; now cleanup the stack and return to the transfer code.
move.l xPC(a0),d0 ; get pc where buserr occurred
addq #2,d0 ; adjust the pc to point to the next instruction <H4>
; Fake a format code 0 exception frame (4 words) to finish cleaning up
clr.w PD3+2(a0) ; stuff a format code 0 (format code is really only a word)
move.l d0,PD2+2(a0) ; stuff the new pc in stack
move.w xSR(a0),PD2(a0) ;
clr.w BIOS_PDMA(a1) ; clear the status register
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
movem.l (sp)+, savedRegs ; restore regs
addq.l #4, sp
addq.l #4, a2 ; adjust user buffer because we manually did the move.l <H4>
@adjR040XFrame ; 040 Bus Error frame-cleaning done here
lea aeXFrameSize-8(sp),sp ; remove 040 Access Error Exception Frame
; but leave PD3 return address
IF RECORD_ON THEN
pea 'RTEr' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
rte ; resume execution at next instruction
@notDataIn ;****************************************
cmp.l #scsiDirectionOut, D0
bne.w @noDataXfer
@1
movem.l D1-D2/A0, -(sp)
bsr Ck4DREQ ;
movem.l (sp)+, D1-D2/A0
bne.s @doWBacks
movem.l D1-D2/A0, -(sp)
bsr Ck4SCSIInt ; see if we have a phase change or something
movem.l (sp)+, D1-D2/A0
bne.w @phzChange ;
bra.b @1
@doWBacks
; clean up the writebacks on the stack frame
move.w WB1S(A0), d0 ; check WB1 for validity
move.l WB1A(A0), A1 ; pass WB Address
move.l WB1D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
@2
movem.l D1-D2/A0, -(sp)
bsr Ck4DREQ ;
movem.l (sp)+, D1-D2/A0
beq.s @2
move.w WB2S(A0), d0 ; check WB2 for validity
move.l WB2A(A0), A1 ; pass WB Address
move.l WB2D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
@3
movem.l D1-D2/A0, -(sp)
bsr Ck4DREQ ;
movem.l (sp)+, D1-D2/A0
beq.s @3
move.w WB3S(A0), d0 ; check WB3 for validity
move.l WB3A(A0), A1 ; pass WB Address
move.l WB3D(A0), d1 ; pass WB Data
bsr.w DoWriteBack ; to routine that takes care of it
; WRITE case for BIOS *********************************
IF RECORD_ON THEN
pea 'BEWT' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
; we have to check the residual register in BIOS....
; 1. if there is a residual word we have to retrieve it, read another word
; with the posted DREQ and nuke the stack to skip the move.l that buserr'd
; 2. if there is no residual then we can just rte like flint!
;
lea BIOSAddr,a1 ; setup for testing BIOS buffer
btst.b #bBIOSW1Cmplt,BIOS_PDMA(a1) ; did one word from the long make it to the c96?
beq.s @doRTE ; 0=no, so restart move.l
;
; Only 1 word of the long word write made it to the controller so we have
; to move the second word manually and increment the buffer pointer.
; Note: the value of a2 will be the value after the move.l postincrement
; so we have to move it backward a word to access the second buffer word.
; We also have to advance the PC so that the rte doesn't restart the faulted
; instruction.
move.l xPC(a0),d0 ; get pc where buserr occurred
; Fake a format code 0 exception frame (4 words) to finish cleaning up
clr.w PD3+2(a0) ; stuff a format code 0 (format code is really only a word)
move.l d0,PD2+2(a0) ; stuff the new pc in stack
move.w xSR(a0),PD2(a0) ;
clr.w BIOS_PDMA(a1) ; clear the status register
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
movem.l (sp)+, savedRegs ; restore regs
addq.l #4, sp
@adjW040XFrame ; 040 Bus Error frame-cleaning done here
lea aeXFrameSize-8(sp),sp ; remove 040 Access Error Exception Frame
;; addq.l #2, a2 ; adjust user buffer because we manually did the move.l <H4>
IF RECORD_ON THEN
pea 'RTEw' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
rte ; resume execution at next instruction
@noDataXfer ;——————
IfDebugStr 'In BEH but not Xfer Direction'
@doRTE
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
IF RECORD_ON THEN
pea 'RTE-' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
movem.l (sp)+, savedRegs ; restore regs
addq.l #4, sp
rte ; restart the move.l
; if phase change or timeout, cleanup and abort the transfer -----
@phzChange
@cleanup
; return SP to the exception stack frame
movem.l (sp)+, savedRegs ; restore regs
addq.l #4, sp ; take scratch space off stack
; get any leftover bytes out of the FIFO if we were doing a FastRead
move.l HALactionPB.ioPtr(A4),a1 ; get the IOPB
move.l scsiFlags(A1), D0
and.l #scsiDirectionMask, D0 ; are we data in or out?
cmp.l #scsiDirectionIn, D0
bne.s @skipLeftovers
move.b rFIFOflags(a3), d0 ; get FIFO status - how many bytes in FIFO
and.w #mFIFOCount, d0 ;
ror.l #1, d0
bra.s @btm0
@top0
move.w rDMA(a3), (a2)+ ; get word from chip and put into user's buffer
@btm0
dbra d0, @top0
tst.l d0
bpl.s @4
move.b rFIFO(a3), (a2)+ ; get byte from chip and put into user's buffer
@4
; get rid of excp'n frame and create a throwaway frame for return to Transfer_96
@skipLeftovers
move.w xSR(sp), d0 ; save SR for new exception frame
bfextu FrameType(sp){0:4}, d1 ; get format code from stack
cmp.b #AEXFrameType, d1 ; check for 040 Access Error Exception Frame
beq.s @Drop040XFrame ; dispose of 040 AE exception frame
cmp.b #shortBEXFrameType, d1 ; short 020/030 exception frame?
bne.s @Drop46w ; no, so use larger frame
adda.w #shortBEXFrameSize, sp ; dispose of the 16-word frame
bra.s @DummyFrame ; and finish up
@Drop040XFrame ; 040 Bus Error frame-cleaning done here
add.w #aeXFrameSize, sp ; remove 040 Access Error Exception Frame
bra.s @DummyFrame ; and create dummy return frame
@Drop46w
add.w #46*2, sp ; size of exception frame
@DummyFrame
; Fake a format code 0 exception frame (4 words) to finish cleaning up
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
clr.w -(sp) ; format code 0
pea FinishErr ; PC value
move.w d0, -(sp) ; sr value
IF RECORD_ON THEN
pea 'RTEp' ;
move.l d0,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
rte ; 'return' from the fake exception
;-----------------
FinishErr
;-----------------
swap d6 ; d6 contains the number of 64k xfers
move.w #0, D6 ; we only care about the high word
moveq #0,d0
move.b rXCM(a3),d0 ; TC regr (most-sig. byte)
lsl.l #8, d0 ; shift to get lower byte from the c96
move.b rXCL(a3),d0 ; TC regr (least-sig. byte) <- d4.b
add.l d0,d6 ; and get the total number of bytes left
move.l d6,d1 ; The number of bytes we didn't transfer...
move.l HALactionPB.ioPtr(A4),a1 ; get the IOPB
move.l scsiFlags(A1), D0
and.l #scsiDirectionMask, D0 ; are we data in or out?
cmp.l #scsiDirectionIn, D0 ; We don't need to check the FIFO if we
; are reading.
beq.b @ErrorDone
moveq.l #mFIFOCount, D0
and.b rFIFOflags(a3), D0 ; how many bytes in FIFO
move.b #cFlushFIFO, rCMD(A3) ; we should flush them out of there
add.l D0,D1 ; we didn't transfer these bytes
sub.l D0,A2 ; adjust the buffer ptr as well
@ErrorDone
moveq.l #scPhaseErr, d0 ; return premature phase change
;
; Remove our bus error handler
;
bsr.w RemoveBEH_BIOS ; get rid of our BEH
IF RECORD_ON THEN
pea 'Ber!' ;
move.l d1,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
rts ; return to the outer Fast Read/Write routine
; or the HAL if no Handshaking goin on.
NAME 'FinishBusErr'
;-----------------
DoWriteBack
;-----------------
move.l a2,-(sp) ; <H4>
btst #bValid, d0 ; if this writeback valid?
beq.s @wbDone ; no - done
and.w #SIZE_MSK, d0 ; yes, transfer proper size
cmp.w #WB_BYTE, d0
bne.s @1
move.B d1, (a1) ; move Byte
bra.s @wbDone
@1
cmp.w #WB_WORD, d0
bne.s @2
move.W d1, (a1) ; move Word
bra.s @wbDone
@2
cmp.w #WB_LONG, d0
bne.s @wbDone
lea BIOSAddr,a2 ; setup for testing BIOS buffer <H4> thru next <H4>
btst.b #bBIOSW1Cmplt,BIOS_PDMA(a2) ; did one word from the long make it to the c96?
bne.s @doWord ;
move.L d1, (a1) ; move LongWord
bra.s @wbDone
@doWord ; <H4> thru next <H4>
move.w d1,(a1) ;
clr.w BIOS_PDMA(a2) ; clear the status register
@wbDone
move.l (sp)+,a2 ; <H4>
rts
ENDWITH
END