boot3/OS/SCSIMgr4pt3/HALc96Routines.a
Elliot Nunn 5b0f0cc134 Bring in CubeE sources
Resource forks are included only for .rsrc files. These are DeRezzed into their data fork. 'ckid' resources, from the Projector VCS, are not included.

The Tools directory, containing mostly junk, is also excluded.
2017-12-26 10:02:57 +08:00

2300 lines
67 KiB
Plaintext

;
; File: HALc96Routines.a
;
; Contains: 53c96 Hardware-Specific routines
;
; Written by: Paul Wolf
;
; Copyright: © 1990-1994 by Apple Computer, Inc., all rights reserved.
;
; Change History (most recent first):
;
; <SM42> 2/3/94 DCB EnableSCSIIRQ was being called when DataDTask didn't run.
; <SM40> 2/1/94 DCB In my last checkin I introduced a re-entrancy problem in the
; deferred task. Now I block 68K ints instead of SCSI its before
; checking the semaphore.
; <SM39> 2/1/94 DCB Addressed a "minor" ordering problem with the DTPending
; semaphore which could cause sync wait hangs if somebody made a
; synchronous request from interrupt time.
; <SM38> 1/31/94 DCB Poured concrete over what I hope are the last remaining holes in
; the Q9x0 dual bus support.
; <SM37> 1/29/94 DCB Fixed several holes for dual bus psuedo DMA machines wherein we
; could clear the int at the VIA and not check the SCSI chip for
; the other bus.
; <SM36> 1/25/94 DCB Whoops, what's a little btst,bne between friends?
; <SM35> 1/25/94 DCB In order to allow our deferred task to run when user code is
; disabled I added a patch to the Deferred Task Manager which
; maintains our own private VM safe deferred task queue.
; <SM34> 1/19/94 DCB Slam interrupts to level 7 before leaving the deferred task.
; This prevents the stack overflow problem reported with the
; installer.
; <SM32> 12/19/93 DCB Major changes. The DeferAndWait function now installs a
; deferred task and then exits the SIM. We re-enter when the
; deferred task executes. This gets rid of the interrupt blocking
; and mouse freezing on pseudo-DMA machines.
; <SM31> 11/22/93 pdw Rolling in from <MCxx>.
; <MC6> 10/29/93 pdw Added the same sort of interrupt level lowering code around the
; call to ReselectISR that I added around the call to MyDT.
; <MC8> 11/8/93 pdw Added support for different inquiry data for different machines.
; <MC5> 10/28/93 pdw Fixed some Target mode stuff. Changed ISRs to drop interrupt
; level to previous level (determined by looking at the actual
; interrupt stack frame).
; <SM30> 11/19/93 chp Vectorize test of SCSI IE. Rework Install_ISR one more time.
; Implement ÒstandardÓ VIA IRQ primitives as subroutines
; (basically copied from macros in HALc96equ.a).
; <SM29> 11/17/93 DCB Changing TestFor_GrandCentralExists so that it works on
; pre-SuperMario ROMs. This is necessary for the INIT version of
; the code.
; <SMG2> 9/22/93 chp Add Grand Central interrupt handler registration mechanism.
; <SM27> 11/8/93 DCB Disabling <SM26> until we get SCSIBusy fixed.
; <SM26> 10/29/93 DCB Using Deferred tasks to drop the interrupt level if we did
; indeed interrupt a level one task.
; <MC5> 10/28/93 pdw Fixed some Target mode stuff. Changed ISRs to drop interrupt
; level to previous level (determined by looking at the actual
; interrupt stack frame).
; <SM25> 10/15/93 DCB Getting rid of a debug trap in the bus error handler.
; <SM24> 10/14/93 pdw <MC> roll-in.
; <MC3> 10/12/93 pdw Added support for Synchronous data transfers, rewrote State
; Machine, message handling etc.
; <MC2> 9/26/93 pdw Changes to G_State usage from bit flags to enumeration.
; <SM23> 9/9/93 pdw Lots of little changes. Name changes, temporary cache_bug
; stuff.
; <SM22> 8/19/93 DCB Improving the bus error handler so that disconnects at
; non-polled bytes will work properly.
; <SM21> 8/13/93 pdw Removed PutXferPhase, instead stuffing phase after every
; interrupt.
; <SM20> 7/20/93 pdw Fixed a Cold Fusion IRQ registration problem by passing in the
; IRQ bit number so that InstallISR knows which slot in VIA2DT to
; use. Changed intDREQbitNum to a byte.
; <SM19> 7/17/93 pdw Lots of little things.
; <SM18> 7/8/93 pdw Changing record data to StkLowPt to help Kurt with debugging
; stack overflow bug.
; <SM17> 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. Resolving
; with my Ludwig sources.
; <SM16> 5/25/93 DCB Rollin from Ludwig. (The next item below)
; <LW11> 5/21/93 PW Added target mode stuff.
; <SM15> 5/6/93 PW Adding NOP to stop asm warnings.
; <SM14> 5/6/93 RC Killed some warnings in the build
; <SM13> 5/5/93 PW Converted names to meanies-friendly names. Updated with latest
; from Ludwig stuff.
; <SM12> 4/8/93 DCB Fixed up the BusErr Handler for Quadras.
; <LW9> 4/14/93 DCB Added parity checking in the interrupt handler.
; <LW8> 3/26/93 PW Changed dreqIn32bit to dreqNeedsSwapMMU and other minor name
; changes.
; <LW7> 3/8/93 PW Removed unnecessary use of D0 for restoring previous interrupt
; level.
; <SM11> 3/22/93 RC Fixed warning problem with useless bne.s
; <SM10> 3/20/93 PW Removed some of the PDMDebug stuff that's not needed.
; <LW6> 2/17/93 PW Added dual-bus/single-interrupt stuff for Quadra support.
; <SM9> 1/31/93 PW Update from the latest of Ludwig. Also changes required for PDM
; (will update Ludwig with these as needed myself).
; <LW5> 1/27/93 PW Disabled dropping of int level to 1 in HAL_ISR to help the old
; call from new call completion hang.
; <LW4> 1/27/93 PW Added HALIntPoll routine. Changed intEnable and intDisable
; calling around - now I disable going into MyDT and enable coming
; out and I disable going into HALAction and enable coming out.
; <LW3> 1/12/93 DCB Fixed the constant ISR! debugger breaks by moving bclr before
; returning int level to previous.
; <LW2> 1/8/93 PW Fixed interrupt reentrancy bug by slamming int level to 7 around
; critical sequence. Also added semaphore to check for reentrant
; ISR. This will not occur unless the level 7 fix is disabled.
; <SM8> 12/5/92 PW Add ability to handle reset interrupts - except for the Curio
; bus.
; <SM7> 10/30/92 DCB Lots of changes to reduce interrupt latency
; <SM6> 10/14/92 PW Removed some unused code and changed some comments.
; <SM5> 10/8/92 PW Lots of trivial name changes.
; <SM4> 8/31/92 PW Changed register and command definitions to reflect changes to
; SCSIEqu53c96.
; <SM3> 8/6/92 PW Added removal of BusErrHandler at the termination of the
; BusErrHandler. It used to be in the second half of Transfer.
; <SM2> 7/28/92 PW Resolved diffs between Clinton's and Paul's sources.
; <SM1> 7/25/92 PW Initial check-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 ;
LOAD 'StandardEqu.d' ; from StandardEqu.a and for building ROMs
INCLUDE 'HardwarePrivateEqu.a' ;
INCLUDE 'UniversalEqu.a'
INCLUDE 'SysPrivateEqu.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
HALc96Routines PROC EXPORT
EXPORT GetReconnectInfo, SizeOfGlobals
EXPORT GetSelectInfo
EXPORT WtForFIFOData
EXPORT Ck4SCSIInt
EXPORT Wt4SCSIInt
EXPORT HALIntPoll, Install_ISR
EXPORT ClearVIASCSIIRQ, EnableVIASCSIIRQ, DisableVIASCSIIRQ, TestVIASCSIIE
EXPORT HAL_SingleISR
EXPORT HAL_DualISR
EXPORT Ck4DREQ
EXPORT BusErrHandler96, InstallBEH96, RemoveBEH96
EXPORT GetInitiatorID, ReadInitiatorID
EXPORT HandleSelected, Disconnected, UnexpectedDisc
EXPORT DataDTask,DeferAndWait
EXPORT ResumeIntRegs, QuickIntCheck, FullIntRegs
EXPORT ci_jDisptch, ci_jDisptch_Vers
IMPORT ENQUEUEHEAD, VMEnableUserCode, VMDisableUserCode
IMPORT DEQUEUETRAP
IMPORT RecordEvent, RecordError, AsmInit53c9xHW
WITH HALc96GlobalRecord
WITH SCSI_IO, HALactions, SCSIPhase
;==========================================================================
SizeOfGlobals ; required for C to Asm connection because we have no complete C global structure
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
move.l #HALc96GlobalRecord.GlobalSize, D0 ; put global size into return value
rts ;
NAME 'SizeOfGlobals'
;==========================================================================
GetReconnectInfo
;_______________________________________________________________________
btst #bReselected, int_rINT(A5) ; reselected int?
beq.s @ck4selected
move.w #HALresult.kHALreselected, HALactionPB.result(A4)
bra.s @valid
@ck4selected
btst #bSelected, int_rINT(A5) ; selected maybe?
beq.s @noSuchThing ; nope, bogus dude!
move.w #HALresult.kHALselectedAsTarget, HALactionPB.result(A4)
@valid
clr.b gotInt(A5) ; we now took care of int
move.b r_selectingID(A5), d0 ; get ID bits (both ours and theirs)
move.b rCF1(a3), d1 ; get our ID number
and.b #$07, d1
bclr d1, d0 ; clear our ID bit (theirs left)
move.w #7, d1
@IDloop
lsl.b #1, d0
dbcs d1, @IDloop ; decrement d1 and loop if not CARRY
bcc.s @noIDonBus ; if no carry then no ID on bus
; bne.s @extraIDonBus ; if not zero, then an extra ID on bus
move.w d1, HALactionPB.selectorID(A4)
moveq.l #iPhaseMsk, d3 ; load mask bits for phase value
and.b rSTA(a3), d3 ; get phase value
move.b D3, currentPhase(A5)
cmpi.b #iMsgIn, d3 ; are we in MsgIn phase still?
bne.s @notMsgInPhase
move.b #SCSIphase.kMessageInPhaseNACK, currentPhase(A5)
btst #bSelected, int_rINT(A5) ; selected int?
bne.s @exit ; -> we're all done
;
; Get the information describing the Reconnect and put into HALactionPB
;
move.b r_selectingMsg1(A5), HALactionPB.msg(A4)
move.b r_selMsgLen(A5), HALactionPB.msgInLen(A4)
move.b r_selPhase(A5), currentPhase(A5) ; update currentPhase
@notMsgInPhase
@exit
rts
;
; Error cases
;
@noIDonBus ; no ID on bus (beside ours)
IfDebugStr 'Reselect with no ID on bus (beside ours)'
bra.s @errorExit
@extraIDonBus ; an extra ID on bus
IfDebugStr 'Reselect with extra ID on bus'
bra.s @errorExit
@noSuchThing
IfDebugStr 'GetReconnectInfo has no info'
@errorExit
cmp.w #HALresult.kHALselectedAsTarget, HALactionPB.result(A4)
beq.s @exit ; if select, leave it as is (ignore bogus ID stuff)
move.w #HALresult.kHALreselectBogus, HALactionPB.result(A4)
bra.s @exit
RTSNAME 'GetReconnectInfo'
;_______________________________________________________________________
GetSelectInfo
IfDebugStr 'GetSelectInfo called! Huh?'
moveq #dsIOCoreErr, D0
_SysError
rts
NAME 'GetSelectInfo'
;_______________________________________________________________________
STRING ASIS
InquiryDataPDM
dc.b $23 ; Processor type, no physical device currently attached
dc.b 0 ; no device-type modifier
dc.b 0 ; might/might not be ISO, ECMA, ANSI standard (not likely)
dc.b 2 ; inquiry data is SCSI-2 compliant
dc.b InquiryDataLen-5
dc.b 0, 0 ; reserved
dc.b 0 ; no RelAdr, WBus32,16, Sync, Linked, CmdQue, SftRe
dc.b 'APPLE ' ; vendor identification
dc.b 'PDM (PDM,CF,CS) '
dc.b '04.3' ; revision level
dc.b '{wolfware} & {gecko}'
InquiryDataLen equ *-InquiryDataPDM
RTSNAME 'InquiryDataPDM'
InquiryDataCyclone
dc.b $23 ; Processor type, no physical device currently attached
dc.b 0 ; no device-type modifier
dc.b 0 ; might/might not be ISO, ECMA, ANSI standard (not likely)
dc.b 2 ; inquiry data is SCSI-2 compliant
dc.b InquiryDataLen-5
dc.b 0, 0 ; reserved
dc.b 0 ; no RelAdr, WBus32,16, Sync, Linked, CmdQue, SftRe
dc.b 'APPLE ' ; vendor identification
dc.b 'Cyclone '
dc.b '04.3' ; revision level
dc.b '{wolfware} & {gecko}'
RTSNAME 'InquiryDataCyclone'
InquiryDataQuadra
dc.b $23 ; Processor type, no physical device currently attached
dc.b 0 ; no device-type modifier
dc.b 0 ; might/might not be ISO, ECMA, ANSI standard (not likely)
dc.b 2 ; inquiry data is SCSI-2 compliant
dc.b InquiryDataLen-5
dc.b 0, 0 ; reserved
dc.b 0 ; no RelAdr, WBus32,16, Sync, Linked, CmdQue, SftRe
dc.b 'APPLE ' ; vendor identification
dc.b 'Quadra '
dc.b '04.3' ; revision level
dc.b '{wolfware} & {gecko}'
RTSNAME 'InquiryDataQuadra'
InquiryDataTNT
dc.b $23 ; Processor type, no physical device currently attached
dc.b 0 ; no device-type modifier
dc.b 0 ; might/might not be ISO, ECMA, ANSI standard (not likely)
dc.b 2 ; inquiry data is SCSI-2 compliant
dc.b InquiryDataLen-5
dc.b 0, 0 ; reserved
dc.b 0 ; no RelAdr, WBus32,16, Sync, Linked, CmdQue, SftRe
dc.b 'APPLE ' ; vendor identification
dc.b 'TNT '
dc.b '04.3' ; revision level
dc.b 'wolfwaregeckocraiger'
RTSNAME 'InquiryDataTNT'
SenseData
dc.b $70 ; current error
dc.b 0 ; no segment number
dc.b $05 ; Sense Key = Illegal Request
dc.b 0,0,0,0 ; Information (none)
dc.b SenseDataLen-8
dc.b 0,0,0,0 ; Command-specific information
dc.b $25 ; ASC = Logical Unit Not Supported
dc.b 0 ; ASCQ = 0
dc.b 0 ; no FRU code
dc.b 0,0,0 ; sense-key specific (none)
SenseDataLen equ *-SenseData
RTSNAME 'SenseData'
STRING PASCAL
;_______________________________________________________________________
; HandleSelected( HALg)
;
; Inputs: A5 HALg
;
; Outputs: none
;
;
;_______________________________________________________________________
;
HandleSelected
IF RECORD_ON THEN
pea 'Targ' ;
pea '****' ;
bsr RecordEvent
addq.l #8, sp
ENDIF
;
; If cmd is 6 bytes long and we handle it, do so, otherwise, send Ck Cond status
;
move.b rcvdCommandLen(A5), D0
beq @returnCkCondition ; no command received -> return ckCond status
cmp.b #6, D0
bne @returnCkCondition ; not 6 byte cdb -> return ckCond status
move.b rcvdCommand(A5), D0 ; get Command byte
beq @DoTURCommand ; 00 = Test Unit Ready
cmp.b #$12, D0 ; 12 = Inquiry
beq.s @DoInquiryCommand
cmp.b #$03, D0 ; 03 = Request Sense
beq.s @DoRequestSenseCommand
bra @returnCkCondition ; unknown
;
; Inquiry command - send Inquiry data
;
@DoInquiryCommand
tst.b rcvdCommand+1(A5) ; test logical unit and EVPD
bne @returnCkCondition
tst.b rcvdCommand+2(A5) ; test page code
bne.s @returnCkCondition ; either nonzero -> return ck cond status
moveq.l #0, D1
move.b rcvdCommand+4(A5), D1 ; get requested count
cmp.b #InquiryDataLen, D1
bls.s @inqOK
move.b #InquiryDataLen, D1
@inqOK
; This should be changed to be decoder based
cmp.b #dmaTypeAMIC, dmaType(A5)
bne.s @cyclone
lea InquiryDataPDM, A0 ; point to our inquiry data
bra.s @sendData
@cyclone
cmp.b #dmaTypePSC, dmaType(A5)
bne.s @quadra
lea InquiryDataCyclone, A0 ; point to our inquiry data
bra.s @sendData
@quadra
cmp.b #dmaTypeNone, dmaType(A5)
bne.s @tnt
lea InquiryDataQuadra, A0 ; point to our inquiry data
bra.s @sendData
@tnt
; cmp.b #dmaTypeGC, dmaType(A5)
; bne.s @
lea InquiryDataTNT, A0 ; point to our inquiry data
bra.s @sendData
;
; Request Sense command - send Sense data
;
@DoRequestSenseCommand
moveq.l #0, D1
move.b rcvdCommand+4(A5), D1 ; get requested count
cmp.b #SenseDataLen, D1
bls.s @senseOK
move.b #SenseDataLen, D1
@senseOK
lea SenseData, A0 ; point to our request sense data
bra.s @sendData
;
; Send the D0 number of data bytes from address A0 by loading each into the FIFO
; then issuing the cSendData command and waiting for the interrupt. When complete,
; send good status and CmdComplete message.
;
@sendDataTop
nop
move.b (A0)+, rFIFO(A3)
nop
tst.b rSTA(A3)
nop
move.b #cSendData, rCMD(A3)
nop
@1
tst.b rSTA(A3) ; this is just to avoid ° 'Ck4S' events in tape
bpl.s @1 ; wait for int
bsr Ck4SCSIInt
@sendData
dbra D1, @sendDataTop
bra.s @returnGoodStatus
;
; Test Unit Ready command - send Check condition status
;
@DoTURCommand
@returnCkCondition
move.b #$02, rFIFO(A3)
nop
move.b #$00, rFIFO(A3)
nop
bra.s @TerminateSeq
@returnGoodStatus
move.b #$00, rFIFO(A3) ; status
nop
move.b #$00, rFIFO(A3) ; message
nop
@TerminateSeq
move.b #cTerminateSeq, rCMD(A3)
nop
@2
bsr.s Ck4SCSIInt ; completes with FC and Disc interrupts
beq.s @2
; DoIntRegs takes care of phase
rts
NAME 'HandleSelected'
;_______________________________________________________________________
;
; PCto32Bit
; Inputs: none
; Destroys: A0, D0
; Calls: _Translate24To32
;
; Function: Converts the PC to a 32-bit address.
;
; Routine from EdiskDrvr.a
;_______________________________________________________________________
_Translate24To32 OPWORD $A091 ;
PCto32Bit
move.l (sp), d0 ; put return address in d0
_Translate24to32 ; convert the address to 32-bit mode
move.l d0, (sp) ; save the new return address
rts ;
NAME 'PCto32Bit'
;_______________________________________________________________________
;
; WtForFIFOData - wait for 256mS for the data to show up in the FIFO
;
; a3 -> SCSI chip read base address - SERIALIZED
; d0 <- number of bytes in FIFO (zero if timed out)
; Z <- .eq.=timed out .ne.=bytes available
;
WtForFIFOData
movem.l d1-d2, -(sp)
move.w TimeSCSIDB, d1 ; get # of DBRAs
lsl.l #8, d1 ; multiply by 256
move.l d1, d2 ; ...a 256mS wait
swap d2
@1
moveq.l #mFIFOCount, d0
and.b rFIFOflags(a3), d0 ; read FIFO flags regr
dbne d1, @1 ; loop until data or timeout
dbne d2, @1 ;
movem.l (sp)+,d1-d2
rts ;
NAME 'WtForFIFOData'
;_______________________________________________________________________
;
; Ck4SCSIInt - just check right now (once) for a SCSI intrp.
;
Ck4SCSIInt
IF RECORD_ON and 1 THEN
pea 'Ck4S'
move.l 4(sp), -(sp) ; and caller's addr
bsr RecordEvent
addq.l #8, sp
ENDIF
tst.b gotInt(A5) ; if there was already an interrupt waiting
bne.s @gotSCSIInt ;
bsr DoIntRegs ; check bINT bit rSTA for c96 interrupt
tst.b gotInt(A5) ; check for an int that we care about
beq.s @noSCSIInt ;
@gotSCSIInt
bsr GotSCSIInt
moveq.l #1, D0
rts
@noSCSIInt
moveq.l #0, D0
rts
NAME 'Ck4SCSIInt'
;_______________________________________________________________________
;
; Wt4SCSIInt - infinite loop to wait for a SCSI intrp. <SM7> PDW (the whole routine changed)
;
; Uses: D0, A0, A1, D5 (return)
;
; On exit: D5 = rFOS|rINT|rSQS|rSTA, byte values from the Seq.Step, Status & INT regrs.
;
; CCR.Z, (EQ) means NOT Disconnect interrupt (i.e. either FC or BS)
; CCR.z, (NE) Disconnect interrupt
allOurRegs REG D0-D7/A0-A6
numAllRegs equ 15
Wt4SCSIInt
IF RECORD_ON THEN
pea 'Wt4S'
move.l 4(sp), -(sp) ; and caller's addr
bsr RecordEvent
addq.l #8, sp
ENDIF
tst.b gotInt(A5) ; if reselect occurred during select prelims
bne.w GotSCSIInt ; we would have already had an interrupt
@noIntYet
; ---- save regs on stack
movem.l allOurRegs, -(sp)
bsr DoIntRegs ; check bINT bit rSTA for c96 interrupt
move.w sr, D0
ori.w #$0700, sr ; \/ \/ \/ Block Ints \/ \/ \/
tst.b gotInt(A5) ; if there was no int we should care about
beq.s GoAsyncDude ; bra - go asynchronous (rts to client)
move.w D0, sr ; if we got an int, Unblock ints /\ /\ /\
movem.l (sp)+, allOurRegs
bra.w GotSCSIInt
nop
RTSNAME 'Wt4SCSIInt'
;_______________________________________________________________________
;
GoAsyncDude
bset #waiting4int, intFlags(A5) ; defer if it comes in now
move.w D0, sr ; /\ /\ /\ Unblock ints /\ /\ /\
GoAsyncNeck
move.l sp, suspendedSP(A5) ; suspend SCSI thread
IF DEBUGGING THEN
move.b #2, privStackState(A5)
ENDIF
IF STACK_RECORD_ON THEN
pea 'Pub<'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l publicSP(A5), sp ; resume previous thread
move.l publicStkLowPt(A5), StkLowPt ; resume stack sniffing
IF STACK_RECORD_ON THEN
pea '<Pub'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
moveq.l #0, D0
rts ; return to HALaction (or MyDT if already deferred)
NAME 'GoAsyncDude'
DeferAndWait
movem.l d0-d2/a0-a2,-(sp) ; save some regs
jsr DeferAndWaitInner
movem.l (sp)+,d0-d2/a0-a2 ; restore some regs
rts
; Defer further actions until interrupts are disabled. This is mainly used for data transfer
; which really screws up interrupt latency on pseudo DMA machines.
; IMPORTANT!
; We are using our own deferred task manager!! The real one doesn't operate with VMUserCode
; disabled. The jDisptch vector does get called however if there is something in the queue.
; Therefore we just stuff an entry in the DTQueue which points at an RTS and then when jDisptch
; gets called we take over and run our real deferred task regardless of whether user code is
; disabled.
DeferAndWaitInner
WITH SCSIGlobalsRec
move.w sr, D0 ; what interrupt level are we?
move.w D0, D1
and.w #$700, D1
beq.w ForgetIt ; if 0 -> getouttahere
btst #fromRealInt,dataDTFlags(a5) ; are we here as a result of a real interruptHandlers.a
; generated interrupt? ie is it safe to assume that our
; deferred task is going to be executed?
beq.w ForgetIt ; nope, don't defer
move.l SCSIGlobals, A0 ;
move.l privDTQHead(A0), D0 ; is Q empty?
bne.w ForgetIt ; no -> don't defer
btst #InDTQ, privDTQFlags(A0) ; already in dispatcher?
bne.w ForgetIt ; yes, can't defer
JustDoIt
IF RECORD_ON THEN
pea 'DtDf'
move.l a0, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
tst.l DTskQHdr ; Is there something in the queue?
bne.b @bogus_is_busy ; nope, no need to enqueue it then
lea DTQueue, A1 ; get ptr to real DT queue
lea dataDT_Null(A5), A0 ; get the DT task version that does nothing
; except mark dataDeferStuff clear
bsr.l ENQUEUEHEAD ; add the element
@bogus_is_busy
move.l SCSIGlobals, A0 ;
lea privDTQueue(A0), A1 ; get ptr to our private queue
lea dataDT(A5), A0 ; Get our deferred task record
bset.b #pendingDTask, dataDTFlags(a5) ; Remember that a deferred task is pending
bsr.l ENQUEUEHEAD ; go add element
movem.l allOurRegs, -(sp)
bra.w GoAsyncNeck
DataPollDTask
move.l a5, -(sp)
move.w sr, -(sp) ; for use down below
ori.w #$0700, sr ; \/ \/ \/ Block Ints \/ \/ \/
bclr.b #pendingDTask, dataDTFlags(a5) ; Should we be here?
beq.b @noGo ; nope, don't do anything
DisableSCSIIRQ ; disable scsi ints
move.w (sp)+, sr ; /\ /\ /\ Unblock ints /\ /\ /\
movem.l allOurRegs, -(sp) ; save all of our registers
;a5 is already setup by HalIntPoll
jsr DataDTaskInner ; Magic Stack Switch!
; Since we may have cleared an interrupt for the OTHER bus (9x0) at the VIA we need to
; poll for interrupts on the other bus until we don't have any more.
cmp.b #SHARED_VIA,intTypeSCSI(A5) ; is this a 900?
bne.b @noShare ; nope, good we don't have to do this
bclr #fromRealInt,dataDTFlags(A5) ; remember it is NOT safe to defer our data xfer routine
@0
move.l otherHALg(A5), A5
move.l baseRegAddr(A5), A3 ; A3 points to c96
bsr.w IntCommonFromDeferred
tst.b D0
bne.s @0
@1
move.l otherHALg(A5), A5
move.l baseRegAddr(A5), A3 ; A3 points to c96
bsr.w IntCommonFromDeferred
tst.b D0
bne.s @0 ; repeat until there are 2 no-ints in a row
@noShare
movem.l (sp)+, allOurRegs ; restore our registers
EnableSCSIIRQ ; re-enable ints
move.l (sp)+, a5
rts ; back to HalIntPoll
@noGo
move.w (sp)+, sr ; /\ /\ /\ Unblock ints /\ /\ /\
move.l (sp)+, a5
rts ; back to HalIntPoll
DataDTask
IF RECORD_ON THEN
pea 'Dts>'
move.l a5, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l a5, -(sp)
move.l A1, A5 ; restore globals from dtParm
move.w sr, -(sp) ; for use down below
movem.l allOurRegs, -(sp) ; save all of our registers
; Note that if ints are enabled (ie we are at level 1 or 0 then
; DisableUserCode/Disable Ints needs to be atomic. Otherwise we
; could get an interrupt with user code disabled or if we reversed
; the order of the two we could get a page fault with ints blocked
; either way it could be bad...
ori.w #$0700, sr ; \/ \/ \/ Block Ints \/ \/ \/
bclr.b #pendingDTask, dataDTFlags(a5) ; Should we be here?
beq.w @noDT ; nope, don't do anything
jsr VMDisableUserCode ; disallow page faults
DisableSCSIIRQ ; disable ints
move.w numAllRegs * 4(sp), sr ; /\ /\ /\ Unblock ints /\ /\ /\
IF RECORD_ON THEN
pea 'Dts#'
move.l a5, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
jsr DataDTaskInner ; Magic Stack Switch!
; Since we may have cleared an interrupt for the OTHER bus (9x0) at the VIA we need to
; poll for interrupts on the other bus until we don't have any more.
cmp.b #SHARED_VIA,intTypeSCSI(A5) ; is this a 900?
bne.b @noShare ; nope, good we don't have to do this
bclr #fromRealInt,dataDTFlags(A5) ; remember it is NOT safe to defer our data xfer routine
@0
move.l otherHALg(A5), A5
move.l baseRegAddr(A5), A3 ; A3 points to c96
bsr.w IntCommonFromDeferred
tst.b D0
bne.s @0
@1
move.l otherHALg(A5), A5
move.l baseRegAddr(A5), A3 ; A3 points to c96
bsr.w IntCommonFromDeferred
tst.b D0
bne.s @0 ; repeat until there are 2 no-ints in a row
@noShare
ori.w #$0700, sr ; \/ \/ \/ Block 68K Ints (let DTManager lower it) \/ \/ \/
jsr VMEnableUserCode ; allow page faults
EnableSCSIIRQ ; re-enable SCSI ints at the VIA
@noDT
movem.l (sp)+, allOurRegs ; restore our registers
move.w (sp)+, d0 ; bit bucket old status register
; and let the DT Manager restore the int level
@noGo
IF RECORD_ON THEN
pea 'Dts<'
move.l a5, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l (sp)+, a5
rts ; back to deferred task mgr
DataDTaskInner
move.w sr, D0
ori.w #$0700, sr ; \/ \/ \/ Block Ints \/ \/ \/
IF STACK_RECORD_ON THEN
pea '>Prv'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l StkLowPt, publicStkLowPt(A5) ; remember old StkLowPt
clr.l StkLowPt ; and disable stack sniffer
move.l sp, publicSP(A5) ; suspend interrupt thread
IF DEBUGGING THEN
move.b #3, privStackState(A5)
ENDIF
move.l suspendedSP(A5), sp ; resume SCSI thread
move.w D0, sr ; /\ /\ /\ Unblock ints /\ /\ /\
movem.l (sp)+, allOurRegs ; restore regs that we saved in DeferAndWait
ForgetIt
rts
NAME 'DataDTask'
;______________________________________________________________________
;
; DisptchTsk Patch, mostly stolen from DeferredTaskMgr.a
; Regs D0-D3 and A0-A3 are saved prior to call.
;
;______________________________________________________________________
; This is a patch to the jDisptch vector for the Deferred Task Manager. It works exactly like
; the real deferred task manager except that it doesn't check inVBL before executing the task.
; This allows it to work with VM user code disabled running which obviously we need if we are
; the backing store. If the version tag is in the SCSI globals it is installed. If you want
; to remove it first look at jDisptch. If it is there remove it and stuff your new one in. If
; not then somebody else has chained their own patch in. To get rid of it in this case you should
; change the version number in the globals and use a completely different set of variables in SCSI
; Globals for the private DT Queue etc. Thus if nothing gets enqueued in the old queue the old code
; will never run. This saves some "Am I running code" which is good since this gets executed a lot
; if FileShare or AppleShare is running. Also note that this assumes that nobody is going to do a
; replacement patch to this vector. If they do it will fail heinously.
;
; Note that since we drop the int level after leaving the real deferred task manager we have
; to check to see if any more got enqueued before leaving here.
;
ci_jDisptch_Vers dc.l 'gcko' ; !!! Change this if you modify the patch!
ci_jDisptch
move.l SCSIGlobals, A3 ; get our globals
bset.b #InDTQ,privDTQFlags(A3) ; already in dispatcher?
bne.s @Exit ; yup, run real deferred tasks and get out
bra.b @DspStart ; nope, run our deferred tasks
@DspLoop
movea.l D0,A0 ; else setup ptr for use
lea privDTQueue(A3) ,A1 ; get ptr to queue
jsr DEQUEUETRAP ; dequeue task to be executed
movea.l DTAddr(A0),A2 ; get ptr to first task
movea.l DTParm(A0),A1 ; get optional parameter
andi.w #$F8FF,SR ; enable all ints
jsr (A2) ; and go do task
move.l SCSIGlobals, A3 ; get our globals
@DspStart
ori.w #HiIntMask,SR ; disable all ints
move.l privDTQHead(A3) ,D0 ; get queue head
bne.s @DspLoop ; loop if tasks exist
bclr.b #InDTQ,privDTQFlags(A3) ; clear indicator
@Exit
move.l oldjDisptch(A3), A0 ; get the old jDisptch
jsr (A0) ; and run it.
move.l SCSIGlobals, A3 ; get our globals
btst.b #InDTQ,privDTQFlags(A3) ; are we busy?
bne.b @rts ; yes, get out!
tst.l privDTQHead(A3) ; anything more to do?
bne.b ci_jDisptch ; yep, go do it
@rts
rts ; else exit
NAME 'ci_jDisptch'
ENDWITH ;SCSIGlobalsRec
;_______________________________________________________________________
;
; GotSCSIInt - Come here when:
; 1: Ck4SCSIInt call found an int
; 2: Wt4SCSIInt call found an int already there
; 3: getRegsBack is 'bra'd to, from Wt4 or MyDT
;
GotSCSIInt
clr.b gotInt(A5) ; we now took care of int
IF RECORD_ON THEN
pea 'GotI'
move.l A2, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
IF GROSS_CHECK THEN
btst #bGrossError, int_rSTA(A5)
beq.s @skipGEdebugger
DebugStr 'Gross Error in GotSCSIInt'
@skipGEdebugger
ENDIF
IF PARITY_ENABLED THEN
btst #bParityError,D5 ; check for parity error
beq.s @goodParity
and.b #~mCF1_EnableParity,rCF1(a3) ; reset the parity bit so we don't get more errors
NOT!
move.l a0,-(sp) ; !!! Temp until I figure out if A0 needs to be saved
move.l HALactionPB.ioPtr(A4), A0 ; ptr to SCSI_IO pb
or.w #kBadParity,SIM_IO.ioEvent(a0) ; set the bad parity bit
move.l (sp)+,a0
_debugger
@goodParity
ENDIF
btst #bDisconnected, int_rINT(A5) ; check for disconnected
beq.s @exit ; returns .EQ as well
move.b #kBusFreePhase, currentPhase(A5) ; returns .NE as well
@exit
rts
NAME 'GetRegsBack_GotInt'
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
;
; UnexpectedDisc - return from an unexpected disconnect
;
UnexpectedDisc
move.w #SCResults.scsiUnexpectedBusFree, HALactionPB.result(A4)
rts
;_______________________________________________________________________
;
; Disconnected - does what needs to be done whenever we get a Disc int from c96
;
; Notes: This routine needs to flush the FIFO and then enable reselection.
; The flush may not be needed but should be safe here. It used to be
; performed just before the Select command was sent to the chip but that
; isn't safe because a reselect interrupt could come in while the move.b
; of the cFlushFIFO is executing. This would cause a flushing of the two
; reselection bytes - the (re)selection ID and the first message byte before
; the interrupt routine would have a chance to pull them out of the FIFO.
;
; We also set up the currentPhase here to kBusFree because a later
; reading of the rSTA register cannot determine if the bus is Free or DataÑOut.
;
Disconnected
IF RECORD_ON THEN
pea 'Disc'
move.l sp, -(sp)
; move.w #$00, -(sp)
; move.w busID(A5), -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
RecCmd $01, 'R',$00
move.b #cFlushFIFO, rCMD(a3) ; Flush FIFO
nop
move.b #0, rSyncOffset(A3) ; no sync data anymore
and.b #~mCF3_FastSCSI, rCF3(A3) ; clr fast bit
IF PARITY_ENABLED THEN
and.b #~mCF1_EnableParity,rCF1(a3) ; reset the parity bit
ENDIF
RecCmd $44, 'R',$02
move.b #cEnableR_sel, rCMD(a3) ; enable selection/reselection
eieio
rts
NAME 'Disconnected'
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
;
; HAL_ISR, HALIntPoll
;
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
;
CregsToSave REG D3-D7/A2-A6
NumCRegsToSave EQU 10
; Return 1 if we handled a _real_ interrupt or zero if nothing or just a deferred task
HALIntPoll
movem.l CregsToSave, -(sp)
move.l 4+4*NumCRegsToSave(sp), A5 ; get HALg off of stack (passed by SIMCore)
move.l baseRegAddr(A5), A3 ; a3 points to c96
IF 0 AND RECORD_ON THEN
move.l #'ItP0', D0
add.b 1+busID(A5), D0
move.l D0, -(sp)
move.w sr, -(sp)
move.w $160, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
moveq.l #0, D0 ; default to "didn't handle an interrupt
moveq.l #0, D2 ; OR sr with 0 for NO EFFECT
moveq.l #-1, D3 ; AND sr with FFFF for NO EFFECT
; if SCSI IRQ is disabled that means that SIM/HAL doesn't want to be reentered
jsr ([HALc96GlobalRecord.jvTestSCSIIE,A5])
beq.s @skipDTask
bclr #fromRealInt,dataDTFlags(A5); remember it is NOT safe to defer our data xfer routine
bsr.w InterruptCommon
; Now check to see if we have a pending deferred task in the deferred task queue. If we do
; then we need to execute it since we got here from a sync wait loop and the interrupt level
; may not be reduced any time soon.
;
; Also note that UserCode is disabled here which is why there is a separate function for calling
; the DT from here as opposed to a real Deferred task.
btst.b #pendingDTask, dataDTFlags(a5) ; Are we expecting to execute the dTask?
beq.b @skipDTask
move.l D0, -(sp) ; save return from InterruptCommon
jsr DataPollDTask ; Execute it (and set semaphore so we don't do it again)
move.l (sp)+, D0 ; and restore it.
@skipDTask
IF 0 AND RECORD_ON THEN
move.l #'IP<0', -(sp)
move.l D0, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
movem.l (sp)+, CregsToSave
rts
RTSNAME 'HALIntPoll'
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
; Note:IntRegs reg D0-D3/A0-A3 ; registers saved by InterruptHandlers.a
regsToSave REG D4-D7/A4-A6
NumRegsToSave EQU 7
HAL_DualISR
movem.l regsToSave, -(sp)
move.l 4+4*NumRegsToSave(sp), A5 ; get HALg off of stack (passed by SIMCore)
IF 0 AND RECORD_ON THEN
move.l #'Duo>', -(sp)
move.w sr, -(sp)
move.w $160, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
@0
bsr.w HAL_ISRCommon
move.l otherHALg(A5), A5
tst.b D0
bne.s @0
@1
bsr.s HAL_ISRCommon
move.l otherHALg(A5), A5
tst.b D0
bne.s @0 ; repeat until there are 2 no-ints in a row
IF 0 AND RECORD_ON THEN
move.l #'Duo<',-(sp)
move.l D0, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
movem.l (sp)+, regsToSave
rts
NAME 'HAL_DualISR'
HAL_SingleISR
movem.l regsToSave, -(sp)
IF 0 AND RECORD_ON THEN
move.l #'Sgl>', -(sp)
move.w sr, -(sp)
move.w $160, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l 4+4*NumRegsToSave(sp), A5 ; get HALg off of stack (passed by SIMCore)
bsr.s HAL_ISRCommon
IF 0 AND RECORD_ON THEN
move.l #'Sgl<', -(sp)
move.l D0, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
movem.l (sp)+, regsToSave
rts
NAME 'HAL_SingleISR'
HAL_ISRCommon
IF 0 AND RECORD_ON THEN
move.l #'ISR0', D0
add.b 1+busID(A5), D0
move.l D0, -(sp)
move.w sr, -(sp)
move.w $160, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
bset #fromRealInt,dataDTFlags(A5); remember that it IS safe to defer our data xfer routine
move.l baseRegAddr(A5), A3 ; A3 points to c96
; moveq.l #0, D2 ; OR sr with 0 for NO EFFECT
; moveq.l #-1, D3 ; AND sr with FFFF for NO EFFECT
move.w #$0700, D2 ; OR sr with 0700 for Block All Ints
move.w #$FFFF-$0600, D3 ; AND sr with FFFF for Drop to Level 1
; fall thru to InterruptCommon
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
InterruptCommon
bsr.w DoIntRegs
beq.s @notOurInt ; bra if the intrp isn't for this bus
;ÑÑÑ Check if some code is Waiting for this (i.e. Wt4SCSIInt)
tst.b gotInt(A5) ; if there was no int we should care about
beq.s @gotAnInt ; bra - exit ISR
@check4defer
bclr #waiting4int, intFlags(A5) ; is Wt4SCSIInt waiting for this?
beq.s @gotAnInt ; no -
DisableSCSIIRQ ; disable ints
move.w SR, D0
move.w D0, -(sp) ; save current interrupt level
or.w D2, D0 ; goto level 7 (or no change)
and.w D3, D0 ; then back to level 1 (or no change)
move.w D0, SR ;
bsr MyDT ; HANDLE THE INTERRUPT
move.w (sp)+, SR ; return to level 2 (or whatever)
EnableSCSIIRQ ; enable ints after we come back out
@gotAnInt
moveq.l #1, D0
rts
@notOurInt
moveq.l #0, D0
rts
NAME 'InterruptCommon'
IntCommonFromDeferred ; Same as above but for use from a deferred task
; but is simpler since it doesn't change the
; interrupt levell.
bsr.w DoIntRegs
beq.s @notOurInt ; bra if the intrp isn't for this bus
;ÑÑÑ Check if some code is Waiting for this (i.e. Wt4SCSIInt)
tst.b gotInt(A5) ; if there was no int we should care about
beq.s @gotAnInt ; bra - exit ISR
@check4defer
bclr #waiting4int, intFlags(A5) ; is Wt4SCSIInt waiting for this?
beq.s @gotAnInt ; no -
DisableSCSIIRQ ; disable ints
bsr MyDT ; HANDLE THE INTERRUPT
EnableSCSIIRQ ; enable ints after we come back out
@gotAnInt
moveq.l #1, D0
rts
@notOurInt
moveq.l #0, D0
rts
NAME 'IntCommonFromDeferred'
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
DoIntRegs
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
move.l D1, -(sp) ; save D1
move.w SR, -(sp) ; bump up interrupt level to 7 <LW2> pdw
or.w #$0700, sr
;ÑÑÑÑ Determine if interrupt was for this HBA
move.b rSTA(A3), D1 ; test intrp bit of status regr
bpl itsNotOurInt ; bra if the intrp isn't for this bus
;ÑÑÑÑ Got an interrupt
@isOurInt
cmp.b #EDGE, intSensSCSI(A5) ; if we are EDGE sensitive,
bne.s @1
ClearSCSIIRQ ; clear the VIA int source
@1
;ÑÑÑÑ Get the status and sequence
move.b rCMD(A3), D1 ; D1 = x | x | x | rSQS
;; move.b rSQS(A3), D1 ; D1 = x | x | x | rSQS
move.b rSQS(A3), selectedRegSQS(A5) ; save rSQS for later (minimize changes)
lsl.w #8, D1 ; D1 = x | x | rSQS | x
move.b rSTA(A3), D1 ; D1 = x | x | rSQS | rSTA
swap D1 ; D1 = rSQS | rSTA | x | x
move.b rFIFOflags(A3), D1 ; D1 = rSQS | rSTA | x | rFOS
lsl.w #8, D1 ; D1 = rSQS | rSTA | rFOS | x
; next move.b clears rSQS, rSTA & rINT
move.b rINT(A3), D1 ; D1 = rSQS | rSTA | rFOS | rINT
bne.s @3
IfDebugStr 'no c9x interrupt cause bits set'
moveq #dsIOCoreErr, D0
_SysError
@3
cmp.b #STICKYBIT, intSensSCSI(A5) ; if we are STICKYBIT sensitive
bne.s @2
ClearSCSIIRQ ; clear the VIA int source
@2
move.w (sp)+, SR ; return to original level
ResumeIntRegs ; If we did a quick int check then we may
; need to come here if we got something we
; didn't expect
IF RECORD_ON THEN
move.l D0, -(sp)
move.w sr, D0
lsr.w #8, D0
and.l #$F, D0
add.l #'IRg0', D0
move.l D0, -(sp)
move.l D1, -(sp)
bsr RecordEvent
addq.l #8, sp
move.l (sp)+, D0
ENDIF
IF 0 AND STACK_RECORD_ON THEN
pea 'SP= '
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
IF DEBUGGING THEN
move.l olderRegsRead(A5), oldestRegsRead(A5)
move.l oldRegsRead(A5), olderRegsRead(A5)
move.l newRegsRead(A5), oldRegsRead(A5)
move.l D1, newRegsRead(A5)
ENDIF
;ÑÑÑÑ Normal or NonNormal interrupt? ÑÑÑÑ
move.b D1, D0
and.b #mNonNormalInt, D0
bne.s @nonNormalInt
;ÑÑÑÑ A normal interrupt - fastest path
@normalInt
st.b gotInt(A5)
move.l D1, intRegsRead(A5)
@doneWithRegularInt
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) ; update currentPhase
@doneWithInt
move.l (sp)+, D1 ; get D1 back
moveq.l #1, D0 ; set return value - "interrupt handled"
rts
;ÑÑÑÑ Reselected?
@nonNormalInt
btst #bReselected, D1
beq.s @ck4Illegal
IF RECORD_ON THEN
pea 'Rsl-'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
st.b gotInt(A5)
move.l D1, intRegsRead(A5)
move.b rFIFO(A3), r_selectingID(A5) ; reselecting ID
btst #bBusService, D1 ; was phase message in?
beq.s @gotMsg ; yes -> get message byte
@noMsg
clr.b r_selMsgLen(A5) ; no message
moveq.l #iPhaseMsk, D0 ; calc what phase we are in
and.b int_rSTA(A5), D0
move.b D0, r_selPhase(A5)
bra.s @callReselectISR
@gotMsg
move.b rFIFO(A3), r_selectingMsg1(A5) ; 1st msg byte from recon sequence
move.b #1, r_selMsgLen(A5)
move.b #kMessageInPhaseNACK, r_selPhase(A5)
@callReselectISR
move.l HALc96GlobalRecord.SIMstaticPtr(A5), -(sp) ; push parameter (ptr to SIMglobals)
move.l ReconnectISRptr(A5), A0
jsr (A0)
addq.l #4, sp
IF RECORD_ON THEN
pea '-Rsl'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
bra.s @doneWithInt
;ÑÑÑÑ Illegal Cmd, Selected or ResetDetected?
@ck4Illegal
btst #bIllegalCmd, D1
beq.s @ck4Select
move.l D1, illCmdRegsRead(A5)
bra.s @doneWithInt ; don't do anything with it
@ck4Select
move.l D1, intRegsRead(A5)
btst #bSelected, D1
bne.s selected
btst #bSelectedWAtn, D1
bne.s selected
;ÑÑÑÑ Reset?
IF DEBUGGING THEN
btst #bResetDetected, D1
IfDebugStr 'SCSI Bus Reset detected'
ENDIF
st.b gotInt(A5)
bsr.w AsmInit53c9xHW
move.b #kBusFreePhase, currentPhase(A5) ; update currentPhase
bra.w @doneWithInt
itsNotOurInt
IF RECORD_ON and 0 THEN
pea 'NoIt'
move.l A3, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.w (sp)+, SR ; return to original level
move.l (sp)+, D1 ; get D1 back
moveq.l #0, D0
rts
NAME 'DoIntRegs'
;ÑÑÑÑ Selected as a Target
selected
st.b gotInt(A5)
move.b rFIFO(A3), r_selectingID(A5) ; reselecting ID
btst #bSelected, D1
beq.s @SelectWAtn
;
; Select W/O Atn - decode sequence step to determine how many command bytes we got
;
@SelectWOAtn
clr.b rcvdMessageLen(A5) ; never get any msg w/o atn
move.b rFIFO(A3), r_selectingMsg1(A5) ; null msg byte (c96 filler)
move.b selectedRegSQS(A5), D1 ; get sequence step register
and.b #7, D1
@WOsqs0
bne.s @WOsqs1to7
clr.b rcvdCommandLen(A5) ; didn't get any cmd bytes
bra.w @sqsDn
@WOsqs1to7
bra.w @getCommandBytes ; get however many command bytes
;
; Select W/Atn - decode sequence to determine how many command and msg bytes we got
;
@SelectWAtn
move.b rFIFO(A3), r_selectingMsg1(A5) ; 1st msg byte
move.b r_selectingMsg1(A5), rcvdMessage(A5) ; store here also
move.b selectedRegSQS(A5), D1 ; get sequence step register
and.b #7, D1
@sqs0
bne.s @sqs1
move.b #1, rcvdMessageLen(A5) ; only 1 message byte
clr.b rcvdCommandLen(A5) ; and no command bytes
bra.s @sqsDn
@sqs1
sub.b #1, D1
bne.s @sqs2
move.b #1, rcvdMessageLen(A5) ; only 1 message byte
bra.s @getCommandBytes ; get however many command bytes
@sqs2
sub.b #1, D1
bne.s @sqs3
move.b #1, rcvdMessageLen(A5) ; only 1 message byte
bra.s @getCommandBytes ; get however many command bytes
@sqs3
sub.b #1, D1
bne.s @sqs4
bra.s @forceDisconnect ; no such sequence step
@sqs4
sub.b #1, D1
bne.s @sqs5to7
moveq.l #mFIFOCount, D0
and.b rFIFOflags(A3), D0 ; how many bytes in FIFO
bne.s @sqs4_1
bra.s @forceDisconnect ; at least 2 message bytes
@sqs4_1
sub.b #1, D0 ; 1 byte in FIFO?
bne.s @sqs4_2 ; no -> must be 2 left
move.b #2, rcvdMessageLen(A5) ; 2 message bytes total
move.b rFIFO(A3), rcvdMessage+1(A5) ; 2nd msg byte
bra.s @sqsDn
@sqs4_2
move.b #3, rcvdMessageLen(A5) ; 3 message bytes total
move.b rFIFO(A3), rcvdMessage+1(A5) ; 2nd msg byte
move.b rFIFO(A3), rcvdMessage+2(A5) ; 3rd msg byte
bra.s @sqsDn
@sqs5to7
move.b #3, rcvdMessageLen(A5) ; 3 message bytes total
move.b rFIFO(A3), rcvdMessage+1(A5) ; 2nd msg byte
move.b rFIFO(A3), rcvdMessage+2(A5) ; 3rd msg byte
;; bra.s @getCommandBytes
;
; All remaining bytes in FIFO are the command bytes - get them
;
@getCommandBytes
moveq.l #mFIFOCount, D0
and.b rFIFOflags(A3), D0 ; how many bytes in FIFO
move.b D0, rcvdCommandLen(A5)
lea rcvdCommand(A5), A0
bra.s @cmdLpBtm
@cmdLpTop
move.b rFIFO(A3), (A0)+ ; move cmd byte into rcvdCommand
@cmdLpBtm dbra D0, @cmdLpTop
;
; At this point, we should have gotten everything out of the FIFO from the Select process
;
@sqsDn
moveq.l #mFIFOCount, D0
and.b rFIFOflags(A3), D0 ; how many bytes in FIFO
beq.s @callSIMisr
@forceDisconnect
RecCmd cDisconnect, 'R',$04
move.b #cDisconnect, rCMD(A3)
bra.w @doneWithInt
@callSIMisr
IF RECORD_ON THEN
pea 'Tgt-'
move.l rcvdIDBits(A5), -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l HALc96GlobalRecord.SIMstaticPtr(A5), -(sp) ; push parameter (ptr to SIMglobals)
move.l ReconnectISRptr(A5), a0
jsr (a0)
addq.l #4, sp
IF RECORD_ON THEN
pea '-Tgt'
move.l rcvdCommandLen(A5), -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
@doneWithInt
move.l (sp)+, D1 ; get D1 back
moveq.l #1, D0 ; set return value - "interrupt handled"
rts
RTSNAME 'R_Selected'
QuickIntCheck
;
; Fastest possible way to check for an interrupt from a data xfer routine
; Note we don't clear the int at the VIA in this routine or block ints because
; we are assuming ints are blocked at the VIA!
;
; On Entry
; d0 -> Expected Int
;
; On Exit
; d0 -> return value
; d1 -> the int regs
;
; returns 1 if we got an int
; returns 0 otherwise
moveq #0, D1
move.l #8, D0 ; setup for dbra
@checkInt
move.b rSTA(A3), D1 ; D1 = x | x | x | rSTA
bmi @gotInt ; bra if we got an int
dbra d0, @checkInt ; loop until int or we exceed our threshold
bra.b @noIntYet
@gotInt
lsl.w #8, D1 ; D1 = x | x | rSTA | x
move.b rFIFOflags(A3), D1 ; D1 = x | x | rSTA | rFOS
lsl.l #8, D1 ; D1 = x | rSTA | rFOS | x
; next move.b clears rSQS, rSTA & rINT
move.b rINT(A3), D1 ; D1 = x | rSTA | rFOS | rINT
bne.s @3
IfDebugStr 'no c9x interrupt cause bits set'
moveq #dsIOCoreErr, D0
_SysError
@3
move.l #1, D0
rts
@noIntYet
move.l #0, D0
rts
RTSNAME 'QuickIntCheck'
FullIntRegs
IF RECORD_ON THEN
pea 'FITR'
move.l a3, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
ClearSCSIIRQ ; clear the VIA int source since we haven't
; been doing it in QuickIntCheck
pea @retrn ; return address
move.l D1, -(sp) ; setup stack correctly for doIntRegs
jmp ResumeIntRegs
@retrn bra.w GotSCSIInt ; and handle the int normally
rts
RTSNAME 'FullIntRegs'
;==========================================================================
; At this point, the return address (to the Deferred Task Manager) is the
; only thing on the stack. We first get our globals pointer then restore
; the stack to where it was when we deferred this thing. Then we just
; jmp to GetRegsBack and it restores all of our regs. When the task
; REALLY completes (and does the callback to Machine), it will simply do
; an RTS which will return back to the Deferred Task Manager.
;--------------------------------------------------------------------------
MyDT
IF STACK_RECORD_ON THEN
pea '>Prv'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
move.l StkLowPt, publicStkLowPt(A5) ; remember old StkLowPt
clr.l StkLowPt ; and disable stack sniffer
move.l sp, publicSP(A5) ; suspend interrupt thread
IF DEBUGGING THEN
move.b #3, privStackState(A5)
ENDIF
move.l suspendedSP(A5), sp ; resume SCSI thread
IF STACK_RECORD_ON THEN
pea 'Prv>'
move.l sp, -(sp)
bsr RecordEvent
addq.l #8, sp
ENDIF
movem.l (sp)+, allOurRegs ; restore regs that we saved in Wt4SCSIInt
bra.w GotSCSIInt
RTSNAME 'MyDT'
;=======================================================================
;_______________________________________________________________________
; Install ISR
Install_ISR
move.l XPT_ISRptr(A5), A0 ; we need to install XPT's ISR (it calls ours)
TestFor VIA2Exists
bnz.b @via2SCSI
@gcSCSI cmp.b #GRAND_CENTRAL,intTypeSCSI(A5)
bne.b @xInstISR
lea 0, A1 ; interrupt handler reference constant in A1
moveq #0, D0
move.w intOSNumberSCSI(A5), D0
_GCRegisterHandler
rts
@via2SCSI moveq #0, D0
move.b intIRQbitNum(A5), D0
lea VIA2DT, A1
move.l A0, (A1,D0.W*4) ; called by an intr on the CB2 pin of VIA2
@xInstISR rts
NAME 'Install_ISR'
;_______________________________________________________________________
ClearVIASCSIIRQ
move.b HALc96GlobalRecord.clearIRQvalue(A5), ([HALc96GlobalRecord.intFlagSCSIAddr,A5])
rts
NAME 'ClearVIASCSIIRQ'
;_______________________________________________________________________
EnableVIASCSIIRQ
move.b HALc96GlobalRecord.enableIRQvalue(A5), ([HALc96GlobalRecord.intEnableSCSIAddr,A5])
rts
NAME 'EnableVIASCSIIRQ'
;_______________________________________________________________________
DisableVIASCSIIRQ
move.b HALc96GlobalRecord.disableIRQvalue(A5), ([HALc96GlobalRecord.intEnableSCSIAddr,A5])
rts
NAME 'DisableVIASCSIIRQ'
;_______________________________________________________________________
TestVIASCSIIE
move.b ([HALc96GlobalRecord.intEnableSCSIAddr,A5]), D0
and.b HALc96GlobalRecord.testIRQenableValue(A5), D0
rts
NAME 'TestVIASCSIIE'
;--------------------------------------------------------------------------
;
; Wt4DREQorInt - infinite loop to wait for a DREQ signal or SCSI chip intrp.
; called by DoSelect to determine end of Selection phase (DREQ if success, Int if not)
;
; Uses: d3, d5
;
; Entry:
; --> d1 = phase to wait for (concurrent with DREQ)
;
; Exit:
; <-- d5 = rFOS|rINT|0|rSTA, byte values from the Seq.Step, Status & INT regrs.
; <-- d0 = 1 if DREQ, 0 if Int
;
;-----------------
Wt4DREQorInt
@1
; Check for interrupt first (to avoid unnecessary dog-slow DREQ check)
bsr Ck4SCSIInt
bne.s @gotAnInt ;
; If no Interrupt, check for DREQ
bsr.s Ck4DREQ
beq.s @1 ; no: try again
@gotDREQ
moveq.l #1, d0 ; return value = Got DREQ
bra.s @exit
; Get sequence and FIFO status registers into D5 (already got rSTA)
@gotAnInt
moveq.l #0, d0 ; return value = Got Interrup
@exit
rts ;
NAME 'Wt4DREQorInt'
;_______________________________________________________________________
;
; Ck4DREQ
; This is slow test. If the value of DREQ
; needs to be determined in a transfer loop, use something else.
;
; Trashes:
; D0
;_______________________________________________________________________
;
Ck4DREQ
movem.l D0/D5/A0, -(sp)
tst.b dreqNeedsSwapMMU(A5)
bne.s @32bit
@24bit
move.l dreqAddr(A5), a0 ; dreqAddr contains DREQ regr address
move.b (a0), d5 ; read DAFB regr
bra.s @both
@32bit
bsr PCto32Bit ; use pc relative
moveq #true32B, d0 ; switch to 32-bit mode to look at SCSI config regr
bsr.s SwapMMU ; (sets up d0 with previous mode)
move.l dreqAddr(A5), a0 ; dreqAddr contains DREQ regr address
move.b (a0), d5 ; read DAFB regr
bsr.s SwapMMU ; return to previous mode (in d0)
@both
move.b intDREQbitNum(A5), d0
btst.l d0, d5 ; check for active SCSI DREQ
movem.l (sp)+, D0/D5/A0
rts
NAME 'Ck4DREQ'
;_______________________________________________________________________
;
; SwapMMU
; Swaps MMU into mode specified in D0. Returns previous
; MMUMode in D0.
;
; Registers : D0 affected as above. No others affected.
;
;_______________________________________________________________________
;
SwapMMU movem.l d1/a0, -(sp)
jsr ([jSwapMMU]) ; do it, call _SwapMMUMode jump vector(smashes d1/a0)
movem.l (sp)+, d1/a0
rts
NAME 'SwapMMU'
;_______________________________________________________________________
;
; void ReadInitiatorID( HALg/hwDesc)
;
; Registers : D0,
; A0 are used but not trashed
;
;_______________________________________________________________________
;
ReadInitiatorID
clr.b -(sp) ; make room for data
move.l sp, A0 ; address of PRAM return buffer
move.l #$00010002, D0 ; read 1 byte of PRAM at offset 2
_ReadXPRam ; get the SCSI id of the Mac
moveq.l #0, D0 ; clear D0
move.b (sp)+, D0 ; get PRAM value in low byte
and.b #$07, D0 ; strip away all but ID bits
move.l 4(sp), A0 ; only parm is HALg/hwDescPtr
move.b D0, initiatorID(A0) ; put InitID value into HALglobals
rts
NAME 'ReadInitiatorID'
;_______________________________________________________________________
;
; uchar GetInitiatorID( HALg) C function
;
; Registers : D0 returns ID.
;
;_______________________________________________________________________
;
GetInitiatorID
move.l 4(sp), A1 ; only parm is HALg/hwDescPtr
moveq.l #0, D0 ; clear D0
move.b initiatorID(A1), D0 ; return InitID value in low byte
rts
NAME 'GetInitiatorID'
;___________________________________________________________________________
;
; BusErrHandler
; 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 and not to the routine
; 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.
;
; On the off chance that we get a bus error while in the emulator we need
; to handle 030 style bus error frames as well as 040 style. This implies
; not doing write backs among other things. Since the info might not always
; be accurate in an emulated BERR we might consider never trying to resume
; an instruction but rather always try to RTE out to somewhere else just like
; a phase change.
;
___________________________________________________________________________;
WITH AEXFrame,SCSIGlobalsRec
longBEXFrameType EQU $0A ; long bus cycle fault stack frame (020/030) !!! put in 680x0.a!
faultedAdrs EQU $10 ; offset of Faulted Address for 030
savedRegs REG D0-D2/D5/A0-A1/A5 ; save these registers because we need to use them
savedRSize EQU 7*4 ; # bytes on stack for saved registers
BusErrHandler96
; 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 @ckBus1
move.l pdmaNonSerlzdAddr(A5),d0 ; get the pseudo DMA Address
bfextu FrameType(a0){0:4},d1 ; get format code from stack
cmp.b #AEXFrameType,d1 ; 040 exception frame?
beq.b @do040 ;
cmp.l faultedAdrs(a0),d0 ; compare with faulted address
beq.s @SCSIFault ; if so, start processing the bus error
@do040
cmp.l FaultAddr(A0),d0 ; compare with faulted address
beq.s @SCSIFault ; if so, start processing the bus error
@ckBus1
cmp.l berr_halg1(A1),A5 ; are we talking to our bus 1?
bne.s @notSCSIFault
move.l pdmaNonSerlzdAddr(A5),d0 ; get the pseudo DMA Address
bfextu FrameType(a0){0:4},d1 ; get format code from stack
cmp.b #AEXFrameType,d1 ; 040 exception frame?
beq.b @do040_again ;
cmp.l faultedAdrs(a0),d0 ; compare with faulted address
beq.s @SCSIFault ; if so, start processing the bus error
@do040_again
cmp.l FaultAddr(A0),d0 ; compare with faulted address
beq.s @SCSIFault ; if so, start processing the bus error
; It's not our fault ------
@notSCSIFault
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'
;ÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑÑ
; 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.b @notDataIn
@DataIn ;****************************************
; clean up the writebacks on the stack frame
bfextu FrameType(a0){0:4},d1 ; get format code from stack
cmp.b #AEXFrameType,d1 ; 040 exception frame?
bne.b @wtloop ; nope, don't do writebacks...
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.w @doRTE
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
@notDataIn ;****************************************
cmp.l #scsiDirectionOut, D0
bne.s @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
bfextu FrameType(a0){0:4},d1 ; get format code from stack
cmp.b #AEXFrameType,d1 ; 040 exception frame?
bne.b @doRTE ; nope, don't do writebacks...
; 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
bra.b @doRTE ; rte and retry the instruction
@noDataXfer ;ÑÑÑÑÑÑ
IfDebugStr 'In BEH but not Xfer Direction'
;
; if DREQ, retry the transfer -----
@doRTE
IF RECORD_ON THEN
pea 'Ber<' ;
move.l d4,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
movem.l (sp)+, savedRegs ; restore regs
addq.l #4, sp
rte ; restart
NAME 'BusErrHandlerMID'
; if phase change or timeout, cleanup and abort the transfer -----
; The could happen from a disconnect. We need to calculate the residual length and
; jump back to the Xfer routine and let it figure it out
@phzChange
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 ; we don't want to grab extra bytes from
; the fifo if we are writing.
bne.b @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
@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
IF RECORD_ON THEN
pea 'Ber$' ;
move.l d4,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
move.w savedSR(a5),sr ; /\ /\ /\ Un Block Ints /\ /\ /\
clr.w -(sp) ; format code 0
pea FinishErr ; PC value
move.w d0, -(sp) ; sr value
rte ; 'return' from the fake exception
NAME 'BusErrHandlerBOTTOM'
;-----------------
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 ; return the number of bytes xferred
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
bsr.w RemoveBEH96
IF RECORD_ON THEN
pea 'Ber!' ;
move.l d1,-(sp) ;
bsr RecordEvent
addq.l #8, sp
ENDIF
rts ; return status in d0 to the Transfer routine
NAME 'FinishBusErr'
;-----------------
DoWriteBack
;-----------------
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
move.L d1, (a1) ; move LongWord
@wbDone
rts
ENDWITH
NAME 'DoWriteBack'
InstallBEH96
WITH SCSIGlobalsRec
movem.l D0/A0-A1, -(sp)
move.l SCSIGlobals, A1
move.b numBEHs(A1), D0 ; how many installed?
bne.s @inc ; at least one? -> don't install any more
move.l BusErrVct, yeOldeBusErrVct(A1) ; save previous Bus Error vector
lea BusErrHandler96, A0 ; get address of our BEH
move.l A0, BusErrVct ; put ours in there
@inc add.b #1, D0
move.b D0, numBEHs(A1)
movem.l (sp)+, D0/A0-A1
rts
NAME 'InstallBEH96'
RemoveBEH96
movem.l D0/A0-A1, -(sp)
move.l SCSIGlobals, A1
sub.b #1, numBEHs(A1)
blt.s @aackBEH
bne.s @dontRemove
lea BusErrHandler96, A0 ; get address of our BEH
cmp.l BusErrVct, A0 ; is current one ours?
bne.s @dontRemove ; if not, -> don't remove it
move.l yeOldeBusErrVct(A1), BusErrVct ; restore previous Bus Error vector
@dontRemove
movem.l (sp)+, D0/A0-A1
rts
@aackBEH
_debugger ; AACK! we went negative
RTSNAME 'RemoveBEH96'
;==========================================================================
ENDWITH
ENDWITH
END