; ; Hacks to match MacOS (most recent first): ; ; 8/3/92 Elliot make this change ; 9/2/94 SuperMario ROM source dump (header preserved below) ; ; ; File: SlotMgr.a ; ; Contains: Macintosh Interface to the Slot Manager ; ; Written by: George Norman, June 1, 1986; (rewritten) David Wong, March 12, 1989 ; ; Copyright: © 1986-1993 by Apple Computer, Inc., all rights reserved. ; ; Change History (most recent first): ; ; 11-07-93 jmp Fixed two more bugs in RemoveCard: 1) Made sure that only the ; fAll bit is set when searching for sResources to delete, and 2) ; made sure that all resouces belonging to a particular slot would ; in fact be found (and now not skipped). ; 2/8/93 rab Sync up with Horror. Comments follow: 8/24/92 SWC Fixed a ; bug in RemoveCard: the wrong register was being used. ; 1/20/93 PN Re-roll in PatchGetCString so that d0 get zeroed out correctly. ; 11/18/92 kc Import GetDriverPatch to fix problem introduced by last checkin. ; 11/17/92 kc Add "IF NOT LC930 THEN" around GetDriverPatch to facilitate dead ; code stripping for the LC930 build. ; 09-24-92 jmp Fixed a bug in the GetDevIndex utility where a register was ; being trashed. ; 6/30/92 kc Roll in Horror, comments follow: ;                  •From SlotManagerPatch.a: ; 6/10/92 djw Modify AddCard to execute SecondaryInit's. ; 6/20/92 PN Roll in patchIIciROM.a. Fix a bug in pInitEntry to restore the ; spID before calling _sFindDevBasse ; 5/16/92 kc Roll in Horror. Comments follow: ; •From SlotManager.a: ;

3/18/92 djw Add new calls to support docking code - AddCard, RemoveCard, ; CheckSlot, and GetSRTEntry. ;

3/5/92 djw Replaced InitSlotMgr, InitsRsrcTable, InitPRAMRecs, and ; Primary_Init entries in the table with new routines. ; 11/5/90 CCH Fixed out of range error due to SlotMgrPatch.a moving to second ; half-meg. ; 9/17/90 CCH Patched Slot interrupt jump table in RAM for Eclipse. ; •From smspecial.a: ;

1/7/91 jmp Because of a misplaced label, the sRsrcFlag was only being read ; for Slot $0 devices. ;

12/11/90 HJR Fix a bug in special casing for slot zero: TestForRBV is not ; appropriate since not all machines that need special casing for ; slot zero have an RBV. ; •From smadvanced.a ; 4/23/91 jmp Cleaned up StatLoadPatch comments. ; 4/22/91 CCH Added a patch to StatLoadDrvr to flush the cache after loading ; in slot resources. Also slightly modified the way GetSlotDrvr ; was being patched. ; 3/29/91 CCH Added in a patch to SlotExec to flush the caches before ; executing code read from a NuBus card. ; 11/19/90 jmp Added in patch for GetDriver. ; •From SlotMgrPatches.a ; 4/24/92 HJR Added NiagraVIA2SlotInt and necessary install code for VSC video ; interrupts. ; 04/16/92 jmp Added a routine so that Slot $0 framebuffers can actually use ; the Minor/Major base address offset sResources like other slots ; can. ; 3/18/92 djw Complete CheckSlot call for DBLite docking code. Add AddCard and ; RemoveCard calls ;
02/05/92 jmp Unfortunately, I put some tables in the middle of this file ; that, in Cyclone, will get bigger. So, I moved them from the ; middle of the file into the pad space. Also, I generalized the ; routine that decides whether a DeclROM’s PrimaryInit/Driver ; should be patched by not stopping once I found the version I was ; looking for (e.g., in case we need to patch out versions 1, 2, ; and 3 of the 8•24 card). ;

10/29/91 jmp Added the VerifySlotPatch routine for supporting super sRsrc ; directories in Slot $0. ;

10/22/91 SAM/jmp Discontinued patching out the JMFB PrimaryInit & Driver on the ; Bungee (1.1) version of the 4•8/8•24 Card ROM. From Zydeco-TERROR ROM. ; •From SlotInfo.a ;

3/18/92 djw Add stub entry points for new docking support routines - ; StubAddCard and StubRemoveCard ;

3/6/92 SWC We thank Dave for

(getting it working in under 25 tries…), ; and move the Docking Manager initialization to StartSDeclMgr ; just before running the primary inits so that we can decided ; whether or not to install the built-in LCD driver when DBLite ; (etc.) is inside a docking station and thus the LCD screen is ; not useable. ;

3/5/92 djw Rewrote slot manager initialization code (major routines from ; beginning of file to SecondaryInit) to facilitate new code for ; DBLite docking station. The major change was to modify the ; routines to execute their functions for a single slot instead of ; for every slot. ;

10/29/91 jmp Added a patch to the VerifySlot routine for supporting super ; sRsrc directories in Slot $0. ; 5/5/92 JSM Roll-in changes from Reality: ; <19> 5/4/92 JSM The one check for isUniversal in this file should just be ; forROM. (Dean really didn’t have to do all that work in <17>). ; 3/18/92 RB Added a WITH statement to use video information record. ; 2/20/92 RB Need to switch to 24 bit mode before calling DisposPtr for ; srtRecords in the routine DeleteSRTRec. Made a second pass on ; Terror changes. The Terror code is diferent files and so that ; makes it hard to compare sources. Changed InitSlotPRAM, ; PtrToSlot, pInitEntry, GetBoard, and added MapUnit. ; <18> 1/7/92 RB Rolled in Terror changes. Mainly cache flushing. ; <17> 8/30/91 DTY Define isUniversal here since it’s no longer defined in ; BBSStartup. isUniversal is defined to be 0 for System builds ; because that’s the way it is. It should already be defined for ; the ROM build (in Build, in a {DefOverride}), but define it ; again just to be on the safe side. (It’s inside a check to see ; whether or not it’s defined, so it’s ok to define it again.) ; <16> 6/12/91 LN removed #include 'HardwareEqu.a' ; <15> 3/8/91 djw (BRC #83516) Fix GetCString where in 32 bit mode reg d0 was ; set to 1 and caused an off-by-one count to be returned. ; <14> 12/10/90 djw Modify SlotExec to fix a problem with the 4•8/8•24/GC card's ; secondaryInit code. Add FixTrident routine to do the fix. ; <13> 9/19/90 BG Removed EclipseNOPs from <9>, <10>. 040s are behaving more ; reliably now. ; <12> 7/30/90 BG Removed IF CPU = 040 conditional in preparation for moving from ; Mac040 to Mac32 build. ; <11> 7/20/90 gbm get rid of slot warnings ; <10> 7/19/90 BG Added EclipseNOPs for flakey 040s. ; <9> 7/5/90 CCH Fixed aeStackFrame record for 68040. Also added EclipseNOPs for ; flakey 040s. ; <8> 6/29/90 djw Fix bug in FindDevBase and in SlotPRAM where hasRBV must be true ; or no slot zero. Deleted MapUnit routine (overkill). Modified ; FindDevBase to return a base addr for slot zero even if there is ; no internal video (addr is not mapped). Corrected conditionals ; for ROM and A/UX. Modified bus exception handler to be VM ; friendly (not pop stack frame and jump). Moved SecondaryInit ; code back to SlotMgrInit.a. Added universal support to SlotPRAM ; routines. Modified pGetBoard to accept spId as a parameter. ; <7> 4/2/90 djw Simplify the install and remove routines for bus exception ; handler ; <6> 2/20/90 BG Changed the definition of aeXFrameSize in the 040 bus exception ; handler to reflect the real size of the exception frame. ; <5> 1/21/90 BG Removed 040 AERROR from pBusException. Added routine ; p040BusException to handle 040 bus error exceptions. ; <4> 1/17/90 djw Modifications to build slot mgr with 32bit QD INIT using BBS ; sources. Added Secondary_Init and GetBoard routines from ; SlotMgrInit.a ; <3> 1/11/90 CCH Added include of “HardwarePrivateEqu.a”. ; <2> 1/3/90 BG Changing the quoting on the 040-related AERROR messages to use ; the correct quotes (single, not double). Will fix problem ; related to the AERROR shortly. ; <1.8> 9/18/89 djw Reorganized sources to combine into two source files, to allow ; system 7.0 patch to share the same sources. ; <1.7> 7/14/89 djw NEEDED FOR AURORA: removed sNewPtr. Set findbigdevbase to ; finddevbase because findbigdevbase. Update internal version ; number. macro is in mpw equate files (so just can't get rid of ; the call). ; <1.6> 6/30/89 djw removed pSlotStatus. Modified InitJmpTbl to use relative ; addressed table. Changed sdmjmptbl to use relative addresses for ; the vectors ; <1.5> 6/12/89 djw Removed findbigdevbase ; <1.4> 3/28/89 djw Cleaned up IMPORT statements. Rewrote InitJmpTbl,SlotManager. ; Added dummy routine for unimplemented selectors. Deleted old ; modification history. Added patch support, added old bsr routine ; to jmp tbl now using slotjsr macro. Rewrote slotmgr dispatcher ; <1.3> 3/12/89 djw Added InitJmpTbl from smadvanced, to make the 1.0 patch easier ; to manage. Moved things around a little. Added GetsRsrcPtr. ; <1.2> 2/20/89 djw Added sVersion, SetsRsrcState, InsertSRTRec, delete code to ; switch slotmanager 24 bit mode - make it 32 bit clean. Added ; GetsRsrc, GetTypesRsrc and FindSRTRec. ; <1.1> 11/10/88 CCH Fixed Header. ; <1.0> 11/9/88 CCH Adding to EASE. ; <1.5> 11/7/88 djw Added InitSlotPRAM ; <•1.4> 10/24/88 djw NEW SLOTMANAGER VERSION. Deleted all register names. Rewrote to ; save mmu mode on stack - no longer need to save any registers in ; called slot manager routines. All new IMPORT routine names. ; <•1.3> 9/23/88 CCH Got rid of inc.sum.d and empty nFiles ; <1.2> 2/15/88 BBM added inc.sum.d as a second load file ; <1.1> 2/15/88 BBM modified for mpw 3.0 equates ; <1.0> 2/10/88 BBM Adding file for the first time into EASE… ; Machine MC68020 String Asis Print Off LOAD 'StandardEqu.d' Include 'HardwarePrivateEqu.a' Include 'RomEqu.a' Include 'UniversalEqu.a' Include 'SlotMgrEqu.a' Include 'ComVideoEqu.a' ; <18> rb Print On If (&TYPE('forAUX') = 'UNDEFINED') Then ; equ indicating whether we are <8> forAUX Equ 0 ; ... building for an A/UX patch Endif ;_________________________________________________________________________________________ <1.4> ; SlotManager - slot manager secondary dispatch routine ; ; Vector through the secondary dispatch table for the slot manager to the requested ; routine. ; ; Input : reg D0 = routine selector (word) ; SlotMgr Proc Export SlotManager ; Jump to the selected slot manager routine. DC.B 'slot version 2.3' ; slot manager internal version number <4> SlotManager CMP.W #LastSDMSelt,D0 ; check selector range BHI.S SlotEmpty ; selector(unsigned) > max - error move.l ([SDMJmpTblPtr],d0.w*4),a1 ; get vector from table <1.7> jmp (a1) ; <1.7> ;_________________________________________________________________________________________ <1.4> ; SlotEmpty - unimplemented slot manager trap ; Export SlotEmpty SlotEmpty move.w #smSelOOBErr,d0 ; error - selector out of bounds rts ;========================================================================================= ; smPrinciple ;========================================================================================= ********************************************************************** * * FUNCTION ReadSlotByte : Read Byte. * Return an 8-bit value from the list pointed to by sPointer and * identified by Id. This value is placed in the LSB of the Result * field. * * Parameter block: * -> spsPointer - Points to the list the Byte is in. * -> spId - The Id of the Byte. * <- spResult - The desired byte. * ********************************************************************** ReadSlotByte FUNC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block Status$d0 EQU D0 ;Status of ReadSlotByte ;---------------------------------------------------------------------- ; ReadSlotByte ;---------------------------------------------------------------------- ;BEGIN WITH spBlock ; Initialize MOVE.L spsPointer(spBlkPtr$a0),-(SP) ;Save sPointer. CLR.B spResult+3(spBlkPtr$a0) ;ReadSlotByte <- 0 ; Read the Offset/Data field and assign the Data to ReadSlotByte. _sOffsetData ;Read the Offset/Data field. BNE.S End ;IF Error THEN ; GOTO End MOVE.B spOffsetData+3(spBlkPtr$a0),spResult+3(spBlkPtr$a0) ;ReadSlotByte <- Data[4] MOVEQ #0,Status$d0 ;Status <- NoError ; Exit End MOVE.L (SP)+,spsPointer(spBlkPtr$a0) ;Restore sPointer. RTS ;Return. ENDWITH ;END ReadSlotByte ENDF EJECT ********************************************************************** * * FUNCTION ReadSlotWord : Read Word. * Return a 16-bit value from the list pointed to by sPointer and * identified by Id. This value is placed in the two LSB fields of * the Result field. * * Parameter block: * -> spsPointer - List pointer. Points to the list the Word is in. * -> spId - Id. The Id of the Word in the list. * <- spResult - The desired word. * ********************************************************************** ReadSlotWord FUNC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM block Status$d0 EQU D0 ;Status of ReadSlotWord ;---------------------------------------------------------------------- ; ReadSlotWord ;---------------------------------------------------------------------- ;BEGIN WITH spBlock ; Initialize MOVE.L spsPointer(spBlkPtr$a0),-(SP) ;Save sPointer CLR.W spResult+2(spBlkPtr$a0) ;ReadSlotWord <- 0 ; Read the Offset/Data field and Assign the Data to ReadSlotWord. _sOffsetData ;Read the Offset/Data field. BNE.S End ;IF Error THEN ; GOTO End MOVE.W spOffsetData+2(spBlkPtr$a0),spResult+2(spBlkPtr$a0) ;ReadSlotWord <- Data[3..4] MOVEQ #0,Status$d0 ;Status <- NoError ; Exit End MOVE.L (SP)+,spsPointer(spBlkPtr$a0) ;Restore sPointer. RTS ;Return. ENDWITH ;END ReadSlotWord ENDF EJECT ********************************************************************** * * FUNCTION ReadSlotLong : Read Long * Return a 32-bit value from the list pointed to by sPointer and * identified by Id. This value is placed in the Result field. * * Parameter block: * -> spsPointer - List pointer. Points to the list the Long is in. * -> spId - Id. The Id of the Long in the list. * <- spResult - The desired long. * ********************************************************************** ReadSlotLong FUNC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block Status$d0 EQU D0 ;Status of ReadSlotLong ;---------------------------------------------------------------------- ; ReadSlotLong ;---------------------------------------------------------------------- ;BEGIN WITH spBlock ; Initialize MOVE.L spsPointer(spBlkPtr$a0),-(SP) ;Save sPointer. CLR.L spResult(spBlkPtr$a0) ;ReadSlotLong <- 0 ; Use sReadPBSize to read the Long and move PhyBlkSize to Result. BCLR.B #fCkReserved,spFlags(spBlkPtr$a0) ;Do not check reserved. _sReadPBSize ;Read the long. BNE.S End ;IF Error THEN ; GOTO End MOVE.L spSize(spBlkPtr$a0),spResult(spBlkPtr$a0) ;ReadSlotLong <- PhyBlkSize MOVEQ #0,Status$d0 ;Status <- NoError ; Exit End MOVE.L (SP)+,spsPointer(spBlkPtr$a0) ;Restore sPointer. RTS ;Return ENDWITH ;END ReadSlotLong ENDF EJECT ;_______________________________________________________________________________________ <1.5> ; GetcString - get a C string ; ; Find the cString identified by the id in the given sList. Allocate a pointer ; block on the system heap and copy the string to it. ; ; Input : reg A0 = ptr to spBlock ; Output : none ; ; spBlock : -> spId id of the cString in the list ; -> spsPointer ptr to list ; <- spResult ptr to the cString in RAM ; ; Called : trap dispatcher ; GetcString Proc Export With spBlock movem.l a2-a3,-(sp) move.l spsPointer(a0),-(sp) ; save ptr to the sList move.b spSlot(a0),-(sp) ; save the slot _sFindStruct ; get the ptr to the string bne.s @Done movea.l spsPointer(a0),a3 ; a3 = ptr to the string ; Calculate the step register bset.b #fConsecBytes,spFlags(a0) ; calc for consecutive bytes _sCalcStep bne.s @Done move.l spResult(a0),d1 ; d1 = step register ; Loop and count all the chars in the string so we know how big a block to allocate. moveq #0,d2 ; clear temp reg for NextStep macro movea.l a3,a1 ; a1 = ptr to the string in the decl rom lea @Done,a2 ; set address to jump to if bus error slotjsr InstallBus ; replace sys bus excptn and 32 bit mode moveq #0,d0 ; d0 = length cntr PN @Loop addq.l #1,d0 ; inc the length move.b (a1),d2 ; NUBUS READ - read a char beq.s @EndLoop ; found the end of the string sNextStep d1,d2,a1 ; inc to the next byte in the decl rom bra.s @Loop ;Continue looping @EndLoop move.l d0,spSize(a0) ; set size of string slotjsr RestoreBus ; restore mmu mode and sys bus excptn ; Allocate a non-relocatable block on the current heap to copy the string to movea.l a0,a2 ; save ptr to spBlock _NewPtr ; allocate the memory <1.6> bne.s @Done move.l a0,spResult(a2) ; pass ptr to buf in result field movea.l a2,a0 ; restore a0 = ptr to spBlock move.l a3,spsPointer(a0) ; restore ptr to the string _sReadStruct ; copy the string to the buffer beq.s @Done ; a good return move.l d0,d1 ; an error - save the error code movea.l a0,a1 ; save ptr to spBlock movea.l spsPointer(a1),a0 ; free the allocated pointer _DisposPtr movea.l a1,a0 ; restore a0 = ptr to spBlock move.l d1,d0 ; restore the error code @Done move.b (sp)+,spSlot(a0) ; restore the slot move.l (sp)+,spsPointer(a0) ; restore the ptr to the sList movem.l (sp)+,a2-a3 rts EJECT ;_______________________________________________________________________________________ <1.5> ; GetSlotBlock - get an sBlock on the system heap ; ; Given a pointer to an sList and the id of an sBlock, find and copy the block to ; a non-relocatable block allocated on either the system or current heap. GetSSBlock ; must allocate on the system heap, because video drivers assumes that it does. The ; old slot manager allocated on the current heap. ; ; Input : reg A0 = ptr to spBlock ; Output : none ; ; spBlock : -> spId id of the sBlock in the list ; -> spsPointer ptr to list ; <- spResult ptr to the copy block in ram ; ; Called : trap dispatcher ; GetSlotBlock Proc Export With spBlock move.l spsPointer(a0),-(sp) ; save the spsPointer field bset.b #fCkReserved,spFlags(a0) ; check the reserved byte for zero _sReadPBSize ; read the physical block size bne.s @Done move.l spSize(a0),d0 ; d0 = sBlock size (including length field) subq.l #4,d0 ; size-length field > 0 ? bgt.s @Alloc ; positive block size <1.7> move.w #smNilsBlockErr,d0 ; a bad block size bra.s @Done @Alloc move.l d0,spSize(a0) ; set size of sBlock (minus length field) movea.l a0,a1 ; save ptr to spBlock _NewPtr ,Sys ; on sys heap for video dependency <1.6> bne.s @Done move.l a0,spResult(a1) ; pass ptr to buffer in spResult movea.l a1,a0 ; restore a0 = ptr to spBlock _sReadStruct ; copy the sBlock to memory beq.s @Done ; a good return move.l d0,d1 ; an error - save the error code movea.l a0,a1 ; save ptr to spBlock movea.l spsPointer(a1),a0 ; free the allocated pointer _DisposPtr movea.l a1,a0 ; restore a0 = ptr to spBlock move.l d1,d0 ; restore the error code @Done move.l (sp)+,spsPointer(a0) ;restore ptr to the sList rts ;_______________________________________________________________________________________ <1.5> ; FindSlotStruct - find a structure ; ; Given a pointer to an sList, find the offset field associated with the given id. ; Calculate a pointer from the offset and return the pointer. ; ; Input : reg A0 = ptr to spBlock ; Output : none ; ; spBlock : -> spId id of the sBlock in the list ; <-> spsPointer ptr to list ; returns ptr to structure ; <- spByteLanes by product of offsetdata call ; ; Called : trap dispatcher, jsr ; FindSlotStruct Proc Export With spBlock _sOffsetData ; find and read the offset/data field bne.s @Done _sCalcsPointer ; convert offset to a pointer @Done rts ;_______________________________________________________________________________________ <1.5> ; ReadSlotStruct - read a structure ; ; Given a pointer to a structure, copy the structure into the given buffer, ; ; Input : reg A0 = ptr to spBlock ; Output : none ; ; spBlock : -> spsPointer ptr to list ; -> spSize number of bytes to read ; <-> spResult ptr to buffer to copy structure to ; ; Called : trap dispatcher, jsr ; ReadSlotStruct Proc Export With spBlock, sInfoRecord movem.l d1-d3/a1-a3,-(sp) move.b spSlot(a0),-(sp) ; save spSlot field movea.l spsPointer(a0),a3 ; a3 = ptr to struct to read move.l a3,-(sp) ; save spsPointer field ; Strip the buffer pointer to make sure it's 32 bit clean move.l spResult(a0),d0 ; d0 = buffer ptr _StripAddress move.l d0,-(sp) ; save a copy of ptr to buffer movea.l d0,a1 ; a1 = ptr to the buffer ; Convert the pointer to a slot number _sPtrToSlot ; return a slot number bne.s @Done _sFindsInfoRecPtr ; given the slot, get ptr to sInfoRecord bne.s @Done movea.l spResult(a0),a2 ; reg a2 = ptr to sInfo record ; Calculate the step register for the slot move.b siCPUByteLanes(a2),spByteLanes(a0) ; get byte lane field from sInfo rec bset.b #fConsecBytes,spFlags(a0) ; calc for consecutive bytes _sCalcStep bne.s @Done move.l spResult(a0),d1 ; d1 = step register ; Loop and read the struct into the buffer ; a1 = ptr to buffer, a3 = ptr to struct slotjsr InstallBus ; 32 bit mode and swap bus exception vector moveq #0,d3 ; clear temp register for NextStep macro move.l spSize(a0),d2 ; d2 = number of bytes to read subq.l #1,d2 ; adjust size for dbra loop lea @EndLoop,a2 ; address to jump to if bus error move.w #smUnExBusErr,d0 ; set error return (just in case) @Loop move.b (a3),(a1)+ ; NUBUS READ - copy a byte sNextStep d1,d3,a3 ; inc rom ptr dbra d2,@Loop ; continue moveq #noErr,d0 ; completed ok - set return status @EndLoop slotjsr RestoreBus ; switch back to save mmu mode and bus exception @Done move.l (sp)+,spResult(a0) ; restore ptr to buffer move.l (sp)+,spsPointer(a0) ; restore ptr to structure move.b (sp)+,spSlot(a0) ; restore slot number field movem.l (sp)+,d1-d3/a1-a3 tst.w d0 ; set ccr rts ;========================================================================================= ; smSpecial ;========================================================================================= ********************************************************************** * * FUNCTION ReadInfo : Read Slot Information. * Read the SlotInfo record identified by Slot. * * Parameter block: * -> spSlot - Which slot. * <-> spResult - Pointer to the buffer. * ********************************************************************** ReadSlotInfo FUNC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block. sInfoRec$a EQU A1 ;sInfoArray pointer. BufferPtr$a EQU A2 ;Pointer to the buffer. Status$d0 EQU D0 ;Status Slot$d EQU D1 ;Slot LoopIndex$d EQU D2 ;Loop Index. ;---------------------------------------------------------------------- ; ReadSlotInfo ;---------------------------------------------------------------------- ;BEGIN WITH spBlock,sInfoRecord ; Allocate local vars. MOVEM.L A2,-(SP) ;Save registers MOVE.L spResult(spBlkPtr$a0),BufferPtr$a ;BuferPtr$a <- Pointer to the buffer. MOVE.L BufferPtr$a,-(SP) ;Save spResult. ; Get a pointer to the sInfo Array for the given slot. C10 _sFindsInfoRecPtr ;Find the pointer to the sInfo record. BNE End ;Branch if error. MOVE.L spResult(spBlkPtr$a0),sInfoRec$a ;sInfoRec$a <- pointer to the sInfo record. ; Move the sInfo record to the block. MOVEQ #sInfoRecSize-1,LoopIndex$d ;LoopIndex$d <- sInfoRecSize-1 ;REPEAT Repeat MOVE.B (sInfoRec$a)+,(BufferPtr$a)+ ; sInfoRec(i)+ <- sInfoArray[Slot].(i)+ Until DBF LoopIndex$d,Repeat ;UNTIL LoopIndex < 0 MOVEQ #0,Status$d0 ;Status <- NoError ; Restore locals & return End MOVE.L (SP)+,spResult(spBlkPtr$a0) ;Restore the buffer pointer. MOVEM.L (SP)+,A2 ;Restore registers RTS ;Return ENDWITH ;END ReadSlotInfo ENDF ********************************************************************** * * PROCEDURE SlotDisposPtr : Dispose Pointer * Dispose of the pointer. * * Parameter block: * -> spsPointer - The pointer to be disposed. * ********************************************************************** SlotDisposPtr PROC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block. p$a0 EQU A0 ;Pointer to be disposed by Memory Manager. Status$d0 EQU D0 ;Status ;---------------------------------------------------------------------- ; SlotDisposPtr ;---------------------------------------------------------------------- ;BEGIN WITH spBlock ; Allocate local vars. move.l a0,-(sp) ; <1.7> ; Dispose of the block. MOVE.L spsPointer(a0),a0 ;p <- sPointer _DisposPtr ;DisposPtr(p) BEQ.S End ;IF Good THEN ; GOTO End ;ELSE MOVE.L #smDisposePErr,d0 ; Status <- smDisposeHErr ; Restore spBlkPtr and Return End movea.l (sp)+,a0 ; <1.7> RTS ENDWITH ;END SlotDisposPtr ENDP EJECT ********************************************************************** * * FUNCTION ReadSlotDrvrName : Read the driver name. * Read the sResource name, Append the '.' prefix to this name, * giving the sDriver name. The result is a pointer to a Pascal type * string useable by iocore (_Open). * * Parameter block: * -> spSlot : Slot number. * -> spId : sResource id. * <- spResult : Pointer to the driver name. * ********************************************************************** ReadSlotDrvrName FUNC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block. SourcePtr$a0 EQU A0 ;**Used by _BlockMove. DestPtr$a1 EQU A1 ;**Used by _BlockMove. sRsrcNamePtr$a EQU A2 ;Pointer to sResource name. BufferPtr$a EQU A3 ;Pointer to the buffer. Status$d0 EQU D0 ;Status. ByteCnt$d0 EQU D0 ;**Used by _BlockMove. LensRsrcName$d EQU D1 ;Length of sResource name. IdSave$d EQU D2 ;Save the sResource Id. ;---------------------------------------------------------------------- ; ReadSlotDrvrName ;---------------------------------------------------------------------- ;BEGIN sGetDrvrName WITH spBlock,sInfoRecord ; Save MOVEM.L A2-A3,-(SP) ;Save A2-A3 MOVE.B spId(a0),d2 ;Save Id MOVE.L spResult(a0),a3 ;BuferPtr$a <- Pointer to the buffer. MOVE.L a3,-(SP) ;Save spResult. ; Get sResource Name CLR.B spExtDev(A0) ; was not required for ReadDrvrName <1.4> CLR.L spParamData(A0) ; only look at enabled guys <1.4> _GetsRsrcPtr ; find the ptr to the sRsrc <1.4> BNE.S Err2 MOVE.B #sRsrcName,spId(a0) _sGetcString ;Get the name. BNE.S Err2 MOVE.L spResult(a0),a2 MOVE.L spSize(a0),d1 SUBQ.B #1,d1 ;Adjust length to ignore the nil EOS marker. CMP.L #254,d1 ;IF d1 > 254 THEN BHI.S Err1 ; Set prefix {Prefix = '.', where Len is the length of the string. MOVE.B spSize+3(a0),(a3)+ ;Str -> '' MOVE.B #'.',(a3)+ ;Str -> '.' ; Append the sResource name to the prefix, giving: '.Name' MOVEM.L A0-A1,-(SP) ;Preserve A0-A1, destroyed by _BlockMove. MOVE.L a2,a0 MOVE.L a3,a1 MOVE.L d1,d0 _BlockMove MOVEM.L (SP)+,A0-A1 ;Restore A0-A1, destroyed by _BlockMove. BNE.S Err1 ; sDriver name build was successful. Dispose of sRsrc name string and exit. exg.l a2,a0 ; a0 = ptr to string to dispose <1.7> _DisposPtr ; <1.7> movea.l a2,a0 ; restore a0 = ptr to spBlock <1.7> MOVEQ #0,d0 BRA.S EndGetDrvrName ; Error, Dispose sRsrc name string and exit. Err1 exg.l a2,a0 ; a0 = ptr to string to dispose <1.7> _DisposPtr ; <1.7> movea.l a2,a0 ; restore a0 = ptr to spBlock <1.7> Err2 MOVE.L #smGetDrvrNamErr,d0 ; Exit sGetDrvrName. EndGetDrvrName MOVE.L (SP)+,spResult(a0) ;Restore the buffer pointer. MOVE.B d2,spId(a0) ;Restore Id MOVEM.L (SP)+,A2-A3 ;Restore A2-A3 RTS ;END ReadSlotDrvrName ENDWITH ENDF ;_______________________________________________________________________________________ <1.6> ; FindDevBase - find the slot device base address ; ; Given a slot and id, find the base address. There are 3 possible base addresses, ; each within a different address space. They are the 1Mb, 16Mb, and 256Mb spaces. ; The address returned is determined by a flag in sRsrcFlags, and by whether a ; minor or major base offset record is found. The following permutations are ; possible, and result in the address returned as indicated: ; ; minorbase majorbase address returned ; _________ _________ ________________ ; ; sRsrcFlags missing x Fssxxxxx ; sRsrcFlags missing x sxxxxxxx ; 24 bit x Fssxxxxx ; 24 bit x sxxxxxxx ; 32 bit x Fsxxxxxx ; 32 bit x sxxxxxxx ; ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spSlot ; -> spId Id in list to search for ; <- spResult base address for the given slot ; ; Called : secondary dispatch table ; FindDevBase Proc Export Import FindDevBaseSlot0 With spBlock,sInfoRecord move.l a1,-(sp) move.b spId(a0),-(sp) ; save the id of the sRsrc move.l spParamData(a0),-(sp) ; save ParamData field ; Get the pointer to the sResource clr.l spParamData(a0) ; clear flags field bset.b #fOneSlot,spParamData+3(a0) ; search only one slot slotjsr sGetsRsrc ; only look at enabled sRsrc's bne @Done ; some error moveq.l #0,d2 move.b spSlot(a0),d2 ; d2 = slot number ; Try to get the minor base offset move.b #MinorBaseOS,spId(a0) _sReadLong bne.s @Major ; minor base offset not found move.l spResult(a0),d1 ; d1 = minor base offset and.l #$00ffffff,d1 ; max offset in minor slot space bra.s @FormSmall ; form a 1Mb or 16Mb ptr ; No minor base - try to get the major base offset @Major move.b #MajorBaseOS,spId(a0) _sReadLong bne.s @Done ; major base offset not found - error move.l spResult(a0),d1 ; d1 = major base offset and.l #$0fffffff,d1 ; max offset in major slot space ; Form a major base pointer (256Mb space) : d2 = slot number ror.l #4,d2 ; d2 = s0000000 or.l d1,d2 ; d2 = sxxxxxxx bra.s @RtnBase ; Form a small base pointer (1Mb or 16Mb) - get the sRsrcFlag word to determine which ; d2 = slot number @FormSmall move.l #$f0000000,d0 ; d0 = F0000000 or.l d1,d0 ; d0 = F0xxxxxx bfins d2,d0{4:4} ; d0 = Fsxxxxxx bfins d2,d0{8:4} ; d0 = Fssxxxxx move.l d0,d2 ; d2 = a 24 bit pointer If forROM and Not forAUX then ; <8> ; If slot zero, then map the base address - only needed for minor space. Only video ; currently has a base address for slot zero. If there is no internal video, then ; do not map the base address. tst.b spSlot(a0) ; getting base addr for slot zero ? bne.s @NonZero movea.l UnivInfoPtr,a1 ; point to the ProductInfo record adda.l ProductInfo.VideoInfoPtr(a1),a1 ; point to the VideoInfo record move.l VideoInfo.VRAMLogAddr24(a1),d2 ; 24bit dev base to alias addr for slot zero move.l VideoInfo.VRAMLogAddr32(a1),d1 ; set d1 to 32bit offset if 32bit ptr @NonZero endif ; <8> move.b #sRsrcFlags,spId(a0) ; get flags to determine whether the pointer _sReadWord ; - should be 24 or 32 bit bne.s @RtnBase ; no flag field - default to 24 bit space move.w spResult+2(a0),d0 ; get sRsrc flag word <1.8> btst.l #f32BitMode,d0 ; 32 bit mode flag set? <1.8> beq.s @RtnBase ; not set - use 24 bit address form <1.8> and.l #$ff000000,d2 ; d2 = Fs000000 or.l d1,d2 ; d2 = Fsxxxxxx @RtnBase move.l d2,spResult(a0) ; return the base pointer moveq.l #noErr,d0 ; set a good return @Done move.l (sp)+,spParamData(a0) ; restore spBlock fields move.b (sp)+,spId(a0) movea.l (sp)+,a1 ; <1.8> rts ;========================================================================================= ; smAdvanced ;========================================================================================= ;_______________________________________________________________________________________ <1.6> ; CardChanged - return true if card changed ; ; Return true if a card's PRAM has been initialized (i.e. a card in the slot ; is now different from the previous one). ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot number ; <- spResult 0=false (card same), $ff if card changed ; CardChanged Proc Export with spBlock,sInfoRecord clr.b spResult+3(a0) ;CardChanged <- Flags {True if > 0} _sFindsInfoRecPtr ;Find the pointer to the sInfo record. bne.s @Done ; <1.8> movea.l spResult(a0),a1 ; a1 = pointer to the sInfo record. btst.b #fCardIsChanged,siStatusFlags(a1) sne.b spResult+3(a0) ;spResult <- True if > 0, else false. MOVEQ #0,d0 ;Status <- NoError (No error is possible) @Done rts ; <1.8> Endp EJECT ********************************************************************** * * PROCEDURE SlotExec : Execute * Download the code block, from the list pointed to by sPointer * and identified by Id, to the current heap zone, check revision * level, check CPU field and execute the code. * * Parameter block: * -> spsPointer - Struct pointer. Points to the list the code block is in. * -> spId - The Id of the code block in the list. * -> spsExecPBlk - Pointer to the se block. * ********************************************************************** SlotExec PROC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block. sePBlkPtr$a0 EQU A0 ;se parameter block pointer. ## warning A0 ## Temp$a EQU A1 ;Temporary address register. CodePtr$a EQU A2 ;Pointer to code. CodePtrCopy$a EQU A3 ;Copy of CodePtr (use to dispose ptr). Status$d0 EQU D0 ;Status Revision$d EQU D1 Temp$d EQU D2 ;Temporary data register. Slot$d EQU D3 ;Slot TimeOut$d EQU D4 ;Time-Out value. BRA.S BeginSlotExec ; ;==================================================================== ; ; PROCEDURE Revision2 : Revision-2 ; Handle a header with a revision level of 2. ; ; Vars imported from SlotExec: ; <-> a2 : Pointer to the Header of the code record. ; <-> Status$d0 : Status of this call. ; <- TimeOut$d : Time-out register. ; ;==================================================================== ;BEGIN WITH spBlock,seHeader2 ; Check Revision level. Revision2 CMP.B #sExec2,seRevision(a2) ;IF (CodePtr.seRevision = sExec2) THEN BEQ.S @10 ; GOTO @10 MOVE.L #smCodeRevErr,d0 ;Status <- smCodeRevErr BRA.S EndRev2 ; Check CPU type @10 CMP.B #sCPU68020,seCPUId(a2) ;IF CodePtr.seCPUId = (sCPU68000 OR sCPU68020) THEN BLS.S @20 ; GOTO @20 {CPU type is good, Continue} MOVE.L #smCPUErr,d0 ;Status <- smCPUErr BRA.S EndRev2 ; Get pointer to code @20 ADDQ.L #seCodeOffset,a2 ;CodePtr <- CodePtr + CodePtr.seCodeOffset {Skip to pointer to code} MOVE.L (a2),a1 ;Temp <- CodePtr^ {Offset to code} ADD.L a1,a2 ;CodePtr <- CodePtr + Temp {Now points to top of code} ; Code header is good, clear status and exit. Good2 MOVEQ #0,d0 ; Return. EndRev2 RTS ;Return ENDWITH ;END Revision2 ;---------------------------------------------------------------------- ; SlotExec ;---------------------------------------------------------------------- ;BEGIN WITH spBlock ; Allocate local vars. BeginSlotExec MOVEM.L A2-A3/D3-D4,-(SP) ;Save registers MOVE.L spsPointer(a0),-(SP) ;Save sPointer ; Read the sBlock from the ROM into RAM. Warning - GetsBlock now always allocates ; on the system heap. _sGetBlock ;CodePtr <- Pointer to the code block. BNE.S End ;IF Error THEN ; GOTO End {exit with error} MOVE.L spResult(a0),a2 MOVE.L a2,a3 ;Save a copy for dispose ptr ; WARNING...WARNING...WARNING... ; The routine FixTrident depends on spSize being unchanged from _sGetBlock bsr FixTrident ; kludge to fix a bug in Trident video card ; Decode the revision level of the header and retrieve the necessary data. BSR.S Revision2 ;IF (Error in Rev-2 header) THEN BNE.S DispCode ; GOTO DispCode {Dispose of the code and exit with error} ; Header ok, execute the code. ExecCode MOVEM.L A0-A6/D0-D7,-(SP) ;Save registers JSR ([jCacheFlush]) ;flush the caches <18> rb MOVE.L spsExecPBlk(a0),a0 ;Set pointer to se parameters. JSR (a2) ;Parameters: ->Slot,->Id, plus any extensions. MOVEM.L (SP)+,A0-A6/D0-D7 ;Restore registers MOVEQ #0,d0 ;SlotExec Good, now exit. ; Release memory (created by sGetBlock). DispCode EXG.L d0,d2 ;Save the Status (May be an error) exg.l a3,a0 ; a0 = ptr to dispose <1.7> _DisposPtr ; dispose of the code block <1.7> movea.l a3,a0 ; restore a0 = ptr to spBlock <1.7> EXG.L d2,d0 ;Restore the Status ; Release memory, Clean up stack & return End MOVE.L (SP)+,spsPointer(a0) ;Restore sPointer. MOVEM.L (SP)+,A2-A3/D3-D4 ;Restore registers RTS ;Return ;END SlotExec ;_______________________________________________________________________________________ <14> ; FixTrident - patch 8•24 card problem ; ; This routine is called from SlotExec (_Exec) to detect a code problem in the ; Trident/4•8/8•24/GC video card's secondaryInit code. The Trident card's ; secondaryInit code has a call to _sNextTypesRsrc. Instead of setting "clr.b tbMask(a0)", ; the error is using "clr.b sptbMask", which clears byte $30 in low mem (fortunately benign). ; This fix looks at every sExec block being executed. If it sees a "clr.b $30" next to ; a _sNextTypesRsrc, then it changes the instruction to a "clr.b $30(a0)". ; ; Input : a2 = ptr to sExec sBlock (including an 8 byte header in this case) ; a0 = ptr to spBlock ; ; spBlock : -> spSize size of code block read in ; TridentCodeSize Equ $18e ; size of secondaryInit sBlock TheBadCode Equ 8+$7e ; header+code offset to bad code to patch FixTrident movem.l a0-a1,-(sp) movea.l a2,a1 ; a1 = ptr to beginning of code cmpi.l #TridentCodeSize,spSize(a0) ; same size code block? bne.s @Done ; no - do nothing lea.l CompareTbl,a0 ; get addr of table of values to compare adda.l (a0)+,a1 ; add in offset to code to compare move.w (a0)+,d0 ; get the compare count @Loop cmp.w (a0)+,(a1)+ ; compare the code dbne d0,@Loop ; continue comparing code tst.w d0 ; did we finish the count? bpl.s @Done ; nope - positive count move.w #$4228,TheBadCode(a2) ; change "clr.b $30" to "clr.b $30(a0)" @Done movem.l (sp)+,a0-a1 rts ;_______________________________________________________________________________________ <14> ; Code Comparision Table For Trident Card Fix ; CompareTbl dc.l 8+$7e ; header+code offset into the code to start dc.w 6-1 ; compare 6 words (adjusted for dbra) dc.w $4238 ; "clr.b spTBMask" <--- the bad one dc.w $0030 dc.w $4228 ; "clr.b spExtDev(a0)" dc.w $0033 dc.w $7015 ; "moveq #15,d0" dc.w $a06e ; "_SlotManager" Endwith Endp EJECT ********************************************************************** * * PROCEDURE CalcsPointer : Calculate sPointer * Calculate a pointer to a byte in the declaration ROM, given the * pointer to the current byte and an offset in bytes (to the new * byte if the memory was contiguous). * * Parameter block: * <-> spsPointer - A pointer to the current byte in ROM. * -> spOffsetData - Offset to the desired location. * -> spByteLanes - The ByteLanes value for this slot. * ********************************************************************** CalcsPointer PROC EXPORT ;VAR spBlkPtr$a0 EQU A0 ;Pointer to the SDM parameter block. ROMPtr$a EQU A1 ;Pointer to ROM. Status$d0 EQU D0 ;Status of sNextsRsrc. TheByteLane$d EQU D1 ;The Byte lane you are in. NumByteLanes$d EQU D2 ;The number of byte-lanes used. Index$d EQU D3 ;Index ROMOffset$d EQU D4 ;Number of bytes offset relative to ROM. PCOffset$d EQU D5 ;Number of bytes offset relative to the CPU. Remainder$d EQU D6 ;Number of bytes to do after the coarse calculation. ;---------------------------------------------------------------------- ; CalcsPointer ;---------------------------------------------------------------------- ;BEGIN WITH spBlock,srrBlock,sInfoRecord ; Allocate and Initialize some vars. MOVEM.L D3-D6,-(SP) ;Save registers MOVE.L spsPointer(spBlkPtr$a0),ROMPtr$a ;ROMPtr$a <- Pointer to the present location in ROM. ; Verify ROMPtr$a points to a valid byte-lane (This test could be deleted, but now it helps debug). MOVEQ #0,TheByteLane$d ;TheByteLane$d <- Bits 0 and 1 of ROMPtr$a. MOVE.W ROMPtr$a,TheByteLane$d AND.B #$03,TheByteLane$d BTST.B TheByteLane$d,spByteLanes(spBlkPtr$a0) ;IF (the bit in spByteLanes corresponds to the actual byte lane) THEN BNE.S C20 ; GOTO C20 {Good} ;ELSE MOVE.L #smBadsPtrErr,Status$d0 ; Status$d0 <- smBadsPtrErr BRA.S End ; GOTO End {Exit with error} ; Calculate the number of byte-lanes used per long. C20 MOVEQ #0,NumByteLanes$d MOVEQ #3,Index$d ;FOR Index <- 3 DOWNTO 0 DO For BTST.B Index$d,spByteLanes(spBlkPtr$a0) ; IF (There is a ROM in this byte-lane) THEN BEQ.S EndFor ADDQ #1,NumByteLanes$d ; NumByteLanes$d <- NumByteLanes$d + 1 EndFor DBF Index$d,For ;ENDFOR TST.B NumByteLanes$d ;IF NumByteLanes$d = 0 THEN BNE.S C30 MOVE.L #smByteLanesErr,Status$d0 ; Status$d0 <- smByteLanesErr BRA.S End ; GOTO End {Exit with error} ; Calculate the offset (Coarse calculation, determines offset of ROMOffset$d >= 4 bytes). C30 MOVE.L spOffsetData(spBlkPtr$a0),ROMOffset$d ;ROMOffset$d <- The number of ROM bytes to the desired new position. BTST.L #23,ROMOffset$d ;ROMOffset$d <- ROMOffset$d sign extended (from 24-bits to 32). BEQ.S C35 OR.L #$FF000000,ROMOffset$d C35 MOVE.L ROMOffset$d,PCOffset$d ;PCOffset$d <- ROMOffset$d DIV NumByteLanes$d TDIVS.L NumByteLanes$d,Remainder$d:PCOffset$d LSL.L #2,PCOffset$d ;PCOffset$d <- PCOffset$d * 4 ; Calculate the Offset (fine calculation, adjust offset for remainning offset of < 4 bytes) C40 TST.B Remainder$d ;IF Remainder = 0 THEN BEQ.S C50 ; GOTO C50 {done} BPL.S PlRemainder ;IF Remainder < 0 THEN ; GOTO PlRemainder {Offset is positive} ; Offset is negative. MiRemainder NEG.W Remainder$d ;Remainder$d <- poitive remainder. SUBQ.W #1,Remainder$d ;Adjust Remainder$d for DBF ;REPEAT Repeat_MI SUBQ.B #1,TheByteLane$d ; TheByteLane$d <- the next byte lane (Check all byte lanes 0..3) AND.B #$03,TheByteLane$d SUBQ.L #1,PCOffset$d ; PCOffset$d <- PCOffset$d + 1 BTST.B TheByteLane$d,spByteLanes(spBlkPtr$a0) ; IF (no ROM in this byte lane) THEN BEQ.S Repeat_MI ; GOTO Repeat_MI Until_MI DBF Remainder$d,Repeat_MI ;UNTIL (there have been four rotates) BRA.S C50 ;GOTO C50 {Calculation complete} ; Offset is positive. PlRemainder SUBQ.W #1,Remainder$d ;Adjust Remainder$d for DBF ;REPEAT Repeat_PL ADDQ.B #1,TheByteLane$d ; TheByteLane$d <- the next byte lane (Check all byte lanes 0..3) @10 ADDQ.L #1,PCOffset$d ; PCOffset$d <- PCOffset$d + 1 BTST.B TheByteLane$d,spByteLanes(spBlkPtr$a0) ; IF (no ROM in this byte lane) THEN BEQ.S Repeat_PL ; GOTO Repeat_PL Until_PL DBF Remainder$d,Repeat_PL ;UNTIL (there have been four rotates) ; Calculations complete, offset was calculated successfully, now add it to the current pointer. C50 ADD.L PCOffset$d,spsPointer(spBlkPtr$a0) ;spsPointer <- spsPointer + PCOffset$d MOVEQ #0,Status$d0 ;Status$d0 <- good. ; Restore globals & return End MOVEM.L (SP)+,D3-D6 ;Restore registers RTS ;Return ENDWITH ;END CalcsPointer ENDP EJECT ********************************************************************** * * FUNCTION GetSlotDrvr : Get Driver. * Load a Mac-OS driver into a relocatable block on the system heap. * * Parameter block: * -> spIOFileName - The file name (probably not useful). * -> spSlot - The slot the driver is in. * -> spId - Id of the sResource which contains the driver. * -> spExtDev - Id of the external device (not useful to drivers in Decl ROM). * -> spsExecPBlk - Pointer to any extra parameters useful to the driver * and/or the sLoad record. * <- spResult - Handle/Ptr to the driver. * *** New feature, add if necessary *** see Rich C. <- spFlags - If fDRAMBased is set then is Handle to the driver. * ********************************************************************** GetSlotDrvr FUNC EXPORT ;VAR ParamBlk$a0 EQU A0 ;Parameter block pointer (Used by SDM & _NewHandle) h$a0 EQU A0 ;Pointer to the handle to be disposed of. NewHandRes$a0 EQU A0 ;***Used by _NewHandle spBlkPtr$a EQU A1 ;SDM parameter block. seBlkPtr$a EQU A2 ;SDM parameter block. DrvrHand$a EQU A3 ;Handle to the driver. Status$d0 EQU D0 ;Status Size$d0 EQU D0 ;***Used by _NewHandle StripAddr$d0 EQU D0 ;Strip Address. Temp$d EQU D1 ;Temporary data register SavedId$d EQU D2 ;Saved Id BRA BeginGetSlotDrvr ; EJECT *==================================================================== * FUNCTION DynLoadDrvr : Dynamically Load Driver. * Execute a given block of code to load the driver. This code must * set spResult with a handle to the driver. * * Vars imported from GetSlotDrvr: * Status$d0 * Status$d0 * Temp$d * ParamBlk$a0 * * Parameter block: * -> spSlot - The slot the driver is in. * -> spId - Id of the sResource which contains the driver. * -> spExtDev - Id of the external device (not useful to drivers in Decl ROM). * -> spsExecPBlk - Pointer to any extra parameters useful to the driver * and/or the sLoad record. * <- spResult - Handle to the driver (Set by the sLoad record). * *** New feature, add if necessary *** see Rich C. <- spFlags - If fDRAMBased is set then is Handle to the driver. * *==================================================================== ;---------------------------------------------------------------------- ; DynLoadDrvr ;---------------------------------------------------------------------- ;BEGIN WITH spBlock,FHeaderRec,seBlock ; Initialize. DynLoadDrvr CLR.L spParamData(A0) ; only look at enabled guys <1.4> _GetsRsrcPtr ; find the ptr to the sRsrc <1.4> BNE.S DError ;Branch if error. ; Execute the code to load the driver. MOVE.B #sRsrcLoadRec,spId(ParamBlk$a0) ;Load the driver. _sExec BNE.S DError ;IF SDM error THEN GOTO DError MOVE.L spsExecPBlk(ParamBlk$a0),seBlkPtr$a ;seBlkPtr$a <- pointer to the seBlock TST.W seStatus(seBlkPtr$a) ;Test the status of the sLoad code. BNE.S DError ;Branch if error. MOVE.L seResult(seBlkPtr$a),spResult(ParamBlk$a0) ;Return the handle to the caller. MOVE.B seFlags(seBlkPtr$a),spFlags(ParamBlk$a0) ;Handle or Ptr? See fRAMBased. MOVEQ #0,Status$d0 BRA.S EndDynLoad ;GOTO EndDynLoad ; Error. DError MOVE.L #smsGetDrvrErr,Status$d0 ;Status <- smsGetDrvrErr EndDynLoad ; <1.8> RTS ENDWITH ;END DynLoadDrvr EJECT *==================================================================== * FUNCTION StatLoadDrvr : Statically Load Driver. * Load the driver from the driver directory. * * Vars imported from GetSlotDrvr: * Status$d0 * Temp$d * spBlkPtr$a * ParamBlk$a0 * NewHandRes$a0 * h$a0 * DrvrHand$a * * spsPointer * * Parameter block: * -> spSlot - The slot the driver is in. * -> spId - Id of the sResource which contains the driver. * <- spResult - Handle to the driver (Set by the sLoad record). * *** New feature, add if necessary *** see Rich C. <- spFlags - If fDRAMBased is set then is Handle to the driver. * *==================================================================== ;---------------------------------------------------------------------- ; StatLoadDrvr ;---------------------------------------------------------------------- ;BEGIN WITH spBlock,FHeaderRec ; Get a pointer to the sResource list and find the driver directory. StatLoadDrvr _sRsrcInfo ;Get a pointer to the sResource list. BNE.S SError2 MOVE.B #sRsrcDrvrDir,spId(ParamBlk$a0) ;Find the driver directory. _sFindStruct BNE.S SError2 ; Load the driver into the system heap zone. LoadDrvr MOVE.B #sMacOS68020,spId(ParamBlk$a0) ;Load a MacOS 68020 driver. BSET.B #fCkReserved,spFlags(ParamBlk$a0) ;Check reserved byte of the PBS. _sReadPBSize ;Read the physical block size. BEQ.S @10 ;IF ok THEN ; GOTO @10 MOVE.B #sMacOS68000,spId(ParamBlk$a0) ;Load a MacOS 68000 driver. BSET.B #fCkReserved,spFlags(ParamBlk$a0) ;Check reserved byte of the PBS. _sReadPBSize ;Read the physical block size. BNE.S SError2 ;IF Error THEN ; GOTO End @10 SUBQ.L #4,spSize(ParamBlk$a0) ;Size <- PhyBlkSize - 4 {By pass the physical block size}. MOVE.L spSize(ParamBlk$a0),Size$d0 _ResrvMem ,SYS ;Compact the system heap. BNE.S SError2 ;Branch if error MOVE.L spSize(ParamBlk$a0),Size$d0 ; _NewHandle ,SYS ;Allocate the memory on the system heap. BNE.S SError2 ; GOTO SError2 MOVE.L NewHandRes$a0,DrvrHand$a ;Put the result of _NewHandle into DrvrHand$a. MOVE.L (NewHandRes$a0),StripAddr$d0 ;Dereference. _StripAddress ;Strip the address. MOVE.L StripAddr$d0,spResult(spBlkPtr$a) ;Put the pointer to the block into spResult. MOVE.L spBlkPtr$a,ParamBlk$a0 ;Restore the SDM parameter block pointer. _sReadStruct ;Read the sBlock into the buffer. BNE.S SError1 ;IF error THEN ; GOTO SError1. MOVE.L DrvrHand$a,spResult(ParamBlk$a0) ;Put handle to the driver in spResult. JSR ([jCacheFlush]) ; flush the caches <18> rb MOVEQ #0,d0 BRA.S EndStatLoad ;GOTO end. ; ERRORS ; Error(1): Dispose of the sBlock and restore the zone. SError1 MOVE.L DrvrHand$a,h$a0 _DisposHandle ;Dispose of the handle. ; Error(2): Set Status$d, spResult and exit with error. SError2 MOVE.L spBlkPtr$a,ParamBlk$a0 ;Restore spBlkPtr CLR.L spResult(ParamBlk$a0) ;Result <- nil MOVE.L #smsGetDrvrErr,Status$d0 ;Status <- smsGetDrvrErr EndStatLoad RTS ENDWITH ;END StatLoadDrvr EJECT ;---------------------------------------------------------------------- ; GetSlotDrvr ;---------------------------------------------------------------------- WITH spBlock ; Patch out Drivers for any Apple Cards that need it. BeginGetSlotDrvr MOVEM.L A2-A3,-(SP) ;Save registers MOVE.L ParamBlk$a0,spBlkPtr$a ;Save spBlkPtr MOVE.B spId(ParamBlk$a0),SavedId$d ;Save Id. ; Try to load the driver by executing the code from proper sLoad list in the sRsrc_LoadDir. BSR DynLoadDrvr ;spResult <- DynLoadDrvr(->spSlot,->spId,<-Status) BEQ.S @Done ;Driver was successfully loaded. ; Try to load the driver from the sRsrc_DrvrDir. MOVE.B SavedId$d,spId(ParamBlk$a0) BSR StatLoadDrvr ;spResult <- StatLoadDrvr(->spSlot,->spId,<-Status) ; Clean up and exit @Done MOVE.L spBlkPtr$a,ParamBlk$a0 ;Restore spBlkPtr MOVE.B SavedId$d,spId(ParamBlk$a0) ;Restore Id. MOVEM.L (SP)+,A2-A3 ;Restore registers ExitGetSlotDrvr RTS ENDWith EJECT ;____________________________________________________________________________ ; ; GetDriverPatch and support (called from _SGetDriver). ; ; Entry/Exit: A0 points to spBlock. ; ; Purpose: The purpose of GetDriverPatch is to identify Apple ; Cards whose Driver code is faulty, and execute fixed ; versions from the CPU ROM. It’s job is to ; call GetDevIndex to determine whether the card/device ; pointed to by the incoming spBlock is one that needs ; patching. If so, it attempts to allocate enough space ; for the driver in the system heap, copy it there, and ; then return a handle to the driver in spBlock.spResult. ; If the driver can’t be loaded (e.g., not enough memory), ; the appropriate Slot Manager error is returned. ;____________________________________________________________________________ GetDriverPatch Proc Export With spBlock,LoadTblRec @saveRegs Reg A0/A3-A5/D3-D4 ; Define registers for work/saving, and Movem.l @saveRegs,-(Sp) ; store them on the stack. Link A6,#-spBlockSize ; Get a stack frame. Move.l A0,A3 ; Save spBlockPtr. ; First, look to see if we even need to be attempting to patch the driver on this ; card/device. ; Bsr GetDevIndex ; Get the card/device index into D0. Move.l D0,D3 ; If the device index is negative, then Bmi.s @done ; driver doesn’t need patching. ; Next, check to see that we’re pointing to the sResource that has the driver or ; driver loader in it (i.e., we don’t want to be opening the driver multiple ; times). ; Lea LoadTbl,A1 ; Point to base of LoadTbl. Mulu #LTEntrySize,D3 ; Adjust index. Move.l A1,A0 ; Point to base of LoadTbl. Move.b ltSpID(A0,D3),D0 ; Get spID. Move.b ltSpExtDev(A0,D3),D1 ; Get spExtDev. Moveq #0,D4 ; Clear value holder. Move.b D0,D4 ; Save spID Swap D4 ; and Move.b D1,D4 ; Save spExtDev. Move.l Sp,A0 ; Point to local spBlock. Move.b spSlot(A3),spSlot(A0) ; Get pointer to right sResource list: Move.b spID(A3),spID(A0) ; Need spSlot, spID, and Move.b D4,spExtDev(A0) ; spExtDev. _SRsrcInfo Bne.s @errRtn Swap D4 ; Get spID. Move.b D4,spID(A0) ; Make sure this sResource is the one _SFindStruct ; with the driver in it. Bne.s @errRtn ; Finally, now that we know that we on the right card/device and are looking at the right ; sResource, allocate relocatable space in the System heap and tell the caller where that ; space is. ; Move.l A1,A4 ; Point to base of LoadTbl. Add.l ltAddrOff(A1,D3),A4 ; Add offset to driver and save pointer. Move.l A1,A0 ; Point to base of LoadTbl. Add.l ltSizeOff(A1,D3),A0 ; Add offset to driver size and get pointer. Move.l (A0),D3 ; Save driver size. Move.l D3,D0 ; Compact/Reserve some space for ourselves _ResrvMem ,SYS ; in the System heap. Bne.s @errRtn ; Get out if we couldn’t reserve the space. Move.l D3,D0 ; Attempt to allocate some space in the _NewHandle ,SYS ; System heap. Bne.s @errRtn ; Get out if we couldn’t get the space. Move.l A0,A5 ; Remember allocated handle, and prevent it _HNoPurge ; from being removed. Move.l A4,A0 ; Get address of driver code. Move.l (A5),A1 ; Get address of allocated space. Move.l D3,D0 ; Get size. _BlockMove ; Move driver into allocated space. Move.l A3,A0 ; Restore spBlockPtr. Move.l A5,spResult(A0) ; Return driver handle in spResult. Moveq #0,D0 ; Return noErr. Bra.s @done @errRtn Move.l #smsGetDrvrErr,D0 ; Couldn’t load driver error. @done Unlk A6 ; Restore stack frame. Movem.l (Sp)+,@saveRegs ; Restore registers. Rts ;____________________________________________________________________________ ; ; GetDevIndex ; ; Entry: A0 -- points to spBlock. ; ; Exit: D0 -- contains index (0..n-1) or error value (<0). ; ; Purpose: The purpose of GetDevIndex is to cycle through a table of ; card/device identifiers. If the card/device passed in ; is in the device table, it’s entry is returned. Otherwise, ; a negative number (-1) is returned. This is a utility routine ; called by SlotGetDriverPatch and SlotPrimaryInitPatch. ; ; Note: This routine Jsr’s (Bsr.l’s) to GetSlotDrvr directly due to ; the fact that we might be coming from our patched out version ; of GetSlotDrvr! We need to do this so that we can compare ; the version of the driver on the card with the one we know ; about. This is so that we don’t patch out newer (and ; presumably compatible) versions of the PrimaryInit and Driver. ; ;____________________________________________________________________________ Macro ; Macro for jumping directly int _GetSlotDriver ; GetSlotDrvr (acting like trap dispatcher). Movem.l A1/D1-D2,-(Sp) ; Save registers (A0 i/o, D0 is result). ; jsr OrigGetSlotDrvr ; Make call. Tst.w D0 ; Act like Slot Manager for result. Movem.l (Sp)+,A1/D1-D2 ; Restore registers. EndMacro ; With DevTblRec,spBlock,seBlock Export GetDevIndex GetDevIndex @saveRegs Reg A3-A5/D3-D4 ; Define registers for work/saving, and Movem.l @saveRegs,-(Sp) ; store them on the stack. Link A6,#-spBlockSize ; Get a stack frame. Move.l A0,A3 ; Save current spBlock to simulate sExec. Move.l Sp,A0 ; Point to stack spBlock. Lea DevTbl,A4 ; Point to table of device identifiers. Moveq #0,D3 ; Set entry index to 0. @repeat Move.b spSlot(A3),spSlot(A0) ; Reset spSlot to the one we want. Clr.w spID(A0) ; Start search from top, no external devices. <11> Clr.b spTBMask(A0) ; No mask (i.e., specific search). Move.w category(A4),spCategory(A0) ; Look for: Category, Move.w cType(A4),spCType(A0) ; CType, Move.w drvrSW(A4),spDrvrSW(A0) ; DrvrSW, Move.w drvrHW(A4),spDrvrHW(A0) ; DrvrHW. Clr.l spParamData(A0) ; Look only for enabled sRsrcs. <11> Bset #foneslot,spParamData+3(A0) ; Limit search to this slot only by _GetTypeSRsrc ; using the new & improved routine. Bne.s @until ; If this isn’t the device were looking for, ; then keep going. _GetSlotDriver ; Otherwise, attempt to load driver (for version #). Bne.s @dontPatch ; If it couldn’t be loaded, punt. Move.l spResult(A0),A5 ; Save driver handle (to dispose). Move.l (A5),A0 ; Get driver pointer. Lea drvrName(A0),A0 ; Get driver name. Clr.w D0 ; Clear D0.w (for use as index). Move.b (A0),D0 ; Get the length of the driver name. Addq #2,D0 ; Adjust offset to version field. Bclr #0,D0 ; Adjust offset for word alignment. Move.w (A0,D0.w),D4 ; Save the version number. Move.l A5,A0 ; Get driver handle, and _DisposHandle ; dispose of it. Cmp.w drvrVers(A4),D4 ; If the card’s version ≠ to ours, <11> Bne.s @until ; then keep going. <11>
Move.l D3,D0 ; Otherwise, copy the index into D0, Bra.s @done ; and return. @until Adda #DTEntrySize,A4 ; Point to next entry in table, and Addq #1,D3 ; increment entry index. Tst.w (A4) ; If this isn’t the final entry, then Bne.s @repeat ; keep checking. @dontPatch Moveq #-1,D0 ; Flag that we don’t want to patch. @done Unlk A6 ; Put stack frame back. Movem.l (Sp)+,@saveRegs ; Restore registers. Rts EndWith ;____________________________________________________________________________ ; ; Tables for PrimaryInit & GetDriver patches. ; ; Note: Keep these here and don’t export these labels! ;____________________________________________________________________________ Import TFBDrvr,TFBDrvrSize Import JMFBDrvr,JMFBDrvrSize Import TFBPrimaryInit Import JMFBPrimaryInit Export JsrTbl DevTbl ;Dc.w CatDisplay,TypVideo,DrSwApple,DrHwTFB,0 ; TFB Entry <11> ;Dc.w CatDisplay,TypVideo,DrSwApple,DrHwJMFB,0 ; JMFB Entry <11> ;Dc.w 0 Align 4 LoadTbl ;Dc.l TFBDrvr-LoadTbl ; Start of TFB driver code. ;Dc.l TFBDrvrSize-LoadTbl ; Length. ;Dc.b sRsrcDrvrDir ; TFB’s have an sRsrcDrvrDir. ;Dc.b 0 ; TFB’s are singly deviced. ;Dc.b 0,0 ; Padding. <11> ;Dc.l JMFBDrvr-LoadTbl ; Start of 4•8/8•24 driver code. ;Dc.l JMFBDrvrSize-LoadTbl ; Length. ;Dc.b sRsrcDrvrDir ; 4•8/8•24’s have an sRsrcDrvrDir. ;Dc.b 0 ; 4•8/8•24’s are singly deviced. ;Dc.b 0,0 ; Padding. Align 4 JsrTbl ;Dc.l TFBPrimaryInit-JsrTbl ; TFBPrimaryInit ;Dc.l JMFBPrimaryInit-JsrTbl ; 4•8/8•24 PrimaryInit ;========================================================================================= ; slotinfo ;========================================================================================= ;_______________________________________________________________________________________ ; ReadSlotPRAM - read PRAM associated with a slot ; PutSlotPRAM - write PRAM associated with a slot ; InitSlotPRAM - write PRAM including board and record id's ; ; Read or write the parameter RAM associated with the given slot number. These ; routines handle both internal and external slot PRAM. ; ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; For ReadSlotPRAM : ; spBlock : -> spSlot slot whose PRAM to read ; -> spResult pointer to 8 byte buffer to place PRAM data ; ; For PutSlotPRAM and InitSlotPRAM : ; spBlock : -> spSlot slot whose PRAM to read ; -> spsPointer pointer to 8 byte buffer to place PRAM data ; SlotPRAM PROC EXPORT ReadSlotPRAM EXPORT PutSlotPRAM EXPORT InitSlotPRAM WITH spBlock,slotGlobals ReadSlotPRAM MOVEQ #0,D0 ; clear reg D0 to indicate a read MOVE.L spResult(A0),spParamData(A0) ; temp set = ptr to buffer to read to BRA.S CommonPRAM ; goto shared routine for read and write PutSlotPRAM MOVEQ #1,D0 ; set reg D0 to indicate a write MOVE.L spsPointer(A0),spParamData(A0) ; temp set = ptr to bufr to write from BRA.S CommonPRAM ; goto shared routine for read and write InitSlotPRAM MOVEQ #2,D0 ; set reg D0 to indicate executive write MOVE.L spsPointer(A0),spParamData(A0) ; temp set = ptr to buf to write from CommonPRAM @savedregs Reg d1/d3/a0-a1 ; <8> movem.l @savedregs,-(sp) ; save regs CLR.W D3 MOVE.L D0,D1 ; D1 = indicates which routine executing MOVE.B spSlot(A0),D3 ; D3 = slot number with high byte clear ; Check range for internal slots with PRAM on the motherboard MOVE.W #smSlotOOBErr,D0 ; assume error CMP.B #sLastSlot,D3 BHI.S @Done ; slot number out of range CMP.B #FirstPRAMSlot,D3 ; a motherboard slot? bge.s @InternalPRAM ; good slot - get PRAM ; Slot number is in the expansion chassis range. If an expansion chassis is present, <1.5> ; call a vendor routine, to handle PRAM requests. TST.W ([sInfoPtr],expnSlot) ; is there an expansion chassis ? BEQ.S @Done ; nope - can't handle this slot's PRAM request ; ***** Add code to look for and call PRAM handling code - use sExec ? ***** BRA.S @Done ; should never get to this point ; Setup parameters to read or write PRAM from motherboard @InternalPRAM MOVE.L $18(A0),A1 SUB.B #FirstPRAMSlot,D3 ; convert slot to relative index MULU.W #SizesPRAMRec,D3 ; index to PRAM record for slot ADD.W #SMPRAMTop,D3 ; add offset to slot manager PRAM MOVE.L #SizesPRAMRec<<16,D0 ; move number of bytes to read into high word MOVE.W D3,D0 ; move offset in PRAM into low word movea.l a1,a0 ; setup A0 = ptr to buffer or data <2.1> TST.B D1 ; is this a read or write? BNE.S @WritePRAM ; non-zero - must be a write _ReadXPRAM BRA.S @Done @WritePRAM subq.l #2,d1 ; regular write or executive write? <2.1> BEQ.S @DoWrite ; executive write ADDQ.L #2,A0 ; skip over board and record id sub.l #$20000-2,d0 ; sub two from number of bytes to write (in high word) <2.1> ; add two to offset into PRAM, pass board and record id's @DoWrite _WriteXPRAM @Done movem.l (sp)+,@savedregs ; restore ptr to spBlock RTS ; done ;_______________________________________________________________________________________ <1.5> ; FindsInfoRecPtr - find sInfo record ptr ; ; Given the slot number in an spBlock, return a pointer to the sInfo record in the ; spResult field. The pointer is retrieved from the sInfo vector table. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot number ; <- spResult ptr to sInfo record ; FindsInfoRecPtr PROC EXPORT WITH spBlock ; Verify slot is good moveq.l #0,d0 ; clear register <2.0> MOVE.B spSlot(A0),D0 ; D0 = slot number CMPI.B #sLastSlot,D0 bhi.S @Error ; error - slot number out of range ; Calculate the pointer to the desired record MOVE.L ([sInfoPtr],d0.w*4),spResult(A0) ; get ptr to sInfo record MOVEQ #0,D0 ; sInfo record present - return good status BRA.S @Done @Error MOVE.W #smSlotOOBErr,D0 ; set error return @Done RTS ; end - FindsInfoRecPtr ENDP ;_______________________________________________________________________________________ <1.4> ; GetsRsrcPtr - find the pointer to an sResource list ; FindsRsrcPtr - find the pointer to an enabled sResource List ; ; Given the , return the pointer to the sResource list. This routine ; differs from the original slot manager in that the sResource list pointer is fetched ; from the SRT instead of the sResource directory on the card. This change allows ; fetching pointers to replaced or RAM sResources. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot number ; -> spId sResource id ; <- spsPointer ptr to sResource list ; ; GetsRsrcPtr Only : ; -> spExtDev external device id ; -> spParamData input flag filed ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; bit 1 set = restrict search to single given slot ; clr = search all slots ; bit 2 set = search for next ; clr = search for given ; FindsRsrcPtr PROC EXPORT EXPORT GetsRsrcPtr WITH spBlock,srrBlock CLR.B spExtDev(A0) ; not required by old slot mgr CLR.L spParamData(A0) ; clear flags field GetsRsrcPtr MOVE.L A1,-(SP) ; save reg _FindSRTRec ; get ptr to SRT entry BNE.S @Done ; not found - error MOVEA.L spsPointer(A0),A1 ; A1 = ptr to SRT entry MOVE.L srrsRsrcPtr(A1),spsPointer(A0) ; return ptr to sRsrc @Done MOVEA.L (SP)+,A1 RTS ;_______________________________________________________________________________________ <2.3> ; PtrToSlot - map sPointer to slot number ; ; Given a valid pointer to a slot, map it to the slot number. Both major and minor ; NuBus address space pointers are mapped. The minor slot number must be a 32bit ; NuBus pointer. This routine map change to map into an array of valid slots to ; take into account bus expansion chassis's. A pointer within the size of ; ROMBase (assumed in ROM) is translated into slot 0. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spsPointer the sPointer ; <- spSlot slot number ; PtrToSlot Proc Export With spBlock movem.l d1/a1,-(sp) ; Fail on nil pointer CLR.B spSlot(A0) MOVE #smSlotOOBErr,D0 ; assume nil ptr - set error status MOVE.L spsPointer(A0),D1 ; D1 = sPointer BEQ.S @Done ; nil pointer - error ; Test for slot 0 (host) CMP.L RealMemTop,D1 ; inside RAM = slot 0 BLS.S @OK MOVE.L ROMBase,A1 ; inside ROM (256k) = slot 0 CMP.L A1,D1 BLO.S @NotInRom ADD.L #$40000,A1 CMP.L A1,D1 BLS.S @OK @NotInRom ; Determine the slot ROL.L #4,D1 CLR.B D1 ROL.L #4,D1 BEQ.S @Done CMP.B #sLastSlot,D1 ; good slot number? BHI.S @Done ; must be slot $0F which is bad MOVE.B D1,spSlot(A0) ; return slot number @OK MOVEQ #0,D0 ; set good return @Done TST D0 ; set condition codes movem.l (sp)+,d1/a1 RTS ; done - PtrToSlot ENDP ;_______________________________________________________________________________________ ; ReadFHeader - copy a declaration ROM's format header block ; ; Copy a declaration ROM's format header block into a buffer. The pointer to the ; buffer is an argument. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot to read ; <-> spResult pointer to buffer ; ReadFHeader PROC EXPORT WITH spBlock,sInfoRecord,FHeaderRec movem.l a1-a2,-(sp) MOVE.L spResult(A0),A2 ; A2 = save ptr to buffer _sFindsInfoRecPtr ; ret - spResult(A0) = ptr to sInfo record BNE.S @Done ; error - bad slot MOVE.L spResult(A0),A1 ; A1 = ptr to sInfo record MOVE.W siInitStatusA(A1),D0 ; is there a card installed ? <1.5> BMI.S @Done ; bad status - error <1.5> ; Offset the ROM ptr to the bottom of the format block MOVE.L siROMAddr(A1),spsPointer(A0) ; set ptr to top of ROM MOVE.L #-fhBlockSize+1,spOffsetData(A0) ; set offset to move ptr MOVE.B siCPUByteLanes(A1),spByteLanes(A0) ; set byte lanes field _sCalcsPointer BNE.s @Done ; some error ; Copy format block into RAM MOVE.L A2,spResult(A0) ; set buffer pointer MOVE.L #fhBlockSize,spSize(A0) ; number of bytes to copy _sReadStruct @Done movem.l (sp)+,a1-a2 RTS ; done - ReadFHeader ENDP ;_______________________________________________________________________________________ <1.4> ; CkCardStat - check a card's status ; ; Check a card's status in the sInfo array. If there is no entry for the slot, then ; the card is not installed. If the initStatusA field of the sInfo record is negative, ; then the card status is also bad. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot to get status ; CkCardStat PROC EXPORT WITH spBlock,sInfoRecord MOVE.L A2,-(SP) _sFindsInfoRecPtr ; get ptr to sInfo record BNE.S @CardBad ; error - card not installed MOVEA.L spResult(A0),A2 ; A2 = ptr to sinfo record TST.W siInitStatusA(A2) ; check card's status field BMI.S @CardBad ; error - card status is bad MOVEQ #0,D0 ; card is ok BRA.S @Done @CardBad MOVE.L #smCkStatusErr,D0 ; set bad card status @Done MOVE.L (SP)+,A2 RTS ; done - CkCardStat ;_______________________________________________________________________________________ <1.3> ; SlotVersion - return slot manager version number ; ; Return the slot manager version number. The Mac II 1.0 and 1.2 ROM's are considered ; version 1. The version in the Cobra II is version 2. ; ; Input : reg A0 = ptr to spBlock ; Output : reg A0 = ptr to spBlock ; ; spBlock : <- spResult version number (long) ; <- spPointer nil (in case of future use) ; SlotVersion PROC EXPORT WITH spBlock if forROM then MOVE.L #slotVNum,spResult(A0) else move.l #1,spResult(A0) endif CLR.L spsPointer(A0) MOVEQ #0,D0 ; set a good return RTS ;_______________________________________________________________________________________ ; GetsRsrc - get sResource by id ; NextsRsrc - get next visible sResource by id ; ; Return information on the next sResource starting from the given slot number and ; sResource id. Unused fields in the spBlock are set to zero. The difference between ; GetsRsrc and NextsRsrc, is that NextsRsrc only includes enabled (visible) entries ; in the search. GetsRsrc uses spParamData as a flags field to indicate the type of ; enabled and disabled entries in the search. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : <-> spSlot slot to start looking in ; <-> spId id to start looking from ; <-> spExtDev external device identifier ; <- spsPointer pointer to sResource record ; <- spRefNum driver reference number (if applicable) ; <- spIOReserved ; <- spCategory sType fields ; <- spCType ; <- spDrvrSW ; <- spDrvrHW ; <- spHWDev hardware device id (if applicable) ; ; For GetsRsrc only : ; -> spParamData input flag filed ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; bit 1 set = restrict search to single given slot ; clr = search all slots ; bit 2 set = search for next ; clr = search for given ; ; <- spParamData state of sResource: 0=enabled, 1=disabled ; NextsRsrc PROC EXPORT EXPORT GetsRsrc WITH sInfoRecord,srrBlock,spBlock,SlotRsrcType,srtLink,slotGlobals CLR.L spParamData(A0) ; clear optional flags BSET.B #fnext,spParamData+3(A0) ; search for next SRT entry GetsRsrc MOVE.L A1,-(SP) _FindSRTRec ; search table BNE.S @Error ; some error or not found ; sResource entry found - set parameters and exit MOVEA.L spsPointer(A0),A1 ; pass A1 = ptr to SRT entry slotjsr SrToSpBlock ; fill in spBlock with srrBlock values BRA.S @Done ; sResource was not found @Error MOVE.W #smNoMoresRsrcs,D0 ; set error return @Done MOVE.L (SP)+,A1 TST.W D0 RTS ; done - NextsRsrc ;_______________________________________________________________________________________ <1.5> ; GetTypesRsrc - get sResource by type ; NextTypesRsrc - get next visible sResource by type ; ; Search for an sResource by its type fields - . Mask ; the type fields appropriately by the mask given in the type mask field of the spBlock. ; Return information on the next sResource starting from the given slot number and ; sResource id. Unused fields in the spBlock are set to zero. The difference between ; GetTypesRsrc and NextTypesRsrc, is that NextTypesRsrc only includes enabled (visible) ; entries in the search. GetTypesRsrc uses spParamData as a flags field to indicate the type ; of enabled and disabled entries in the search. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spTBMask sType mask (bit 0-3) - bit set means mask off this field ; <-> spSlot slot to start looking in ; <-> spId id to start looking from ; <-> spExtDev external device identifier ; <- spHWDev hardware device id (if applicable) ; <- spsPointer pointer sResource list (*****different than old slot manager) ; <- spRefNum driver reference number (if applicable) ; <- spIOReserved ; <- spCategory sType fields ; <- spCType ; <- spDrvrSW ; <- spDrvrHW ; ; For GetTypesRsrc only : ; -> spParamData input flag filed ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; bit 1 set = restrict search to single given slot ; clr = search all slots ; ; <- spParamData state of sResource: 0=enabled, 1=disabled ; EXPORT NextTypesRsrc,GetTypesRsrc NextTypesRsrc CLR.L spParamData(A0) ; clear optional flags GetTypesRsrc MOVEM.L D1-D6/A1,-(SP) ; Use the type mask field in the spBlock as an index into a table to get the ; bit mask for the sType fields MOVEQ #0,D0 ; clear for use as index MOVE.B spTBMask(A0),D0 ; D0 = index (mask value) LEA MaskTbl,A1 ; addr of table in reg A1 LSR.B #2,D0 ; use bits <3,2> as index MOVE.L (A1,D0.W*4),D1 ; D1 = mask for MOVE.B spTBMask(A0),D0 ; D0 = index (mask value) AND.B #3,D0 ; use low 2 bits MOVE.L (A1,D0.W*4),D2 ; D2 = mask for MOVE.L spCategory(A0),D3 ; get LONG, D3 = to match MOVE.L spDrvrSW(A0),D4 ; get LONG, D4 = to match AND.L D1,D3 ; mask target AND.L D2,D4 ; mask target ; Search SRT comparing the type fields of the entries to the type we are looking ; for. Mask the entry's type field before doing the compare. ; reg D1 = mask, D2 = mask ; reg D3 = to match, D4 = to match @Loop BSET.B #fnext,spParamData+3(A0) ; search for next SRT entry _FindSRTRec ; search table BNE.S @Done ; no more good entries in the SRT - failed MOVE.L spsPointer(A0),A1 ; get A1 = ptr to SRT entry MOVE.L srrSlot(A1),spSlot(A0) ; update spSlot,spId,spExtDev,spHwDev MOVE.L D1,D5 ; get D5 = copy of mask AND.L srrCategory(A1),D5 ; mask into D5 CMP.L D3,D5 ; match ? BNE.S @Loop ; does not match - get next entry MOVE.L D2,D6 ; get D6 = copy of mask AND.L srrDrvrSw(A1),D6 ; mask into D6 CMP.L D4,D6 ; does fields match ? BNE.S @Loop ; no match - get next entry ; Found the entry - return the sResource information slotjsr SrToSpBlock ; fill in spBlock with srrBlock values MOVEQ #0,D0 ; set good return @Done MOVEM.L (SP)+,D1-D6/A1 RTS ;_______________________________________________________________________________________ <1.3> ; Mask table for NextTypesRsrc ; ; This is a table of bit masks for the fields of ; an sResource. The table is indexed by the spTBMask field of the spBlock. Bits ; <1,0> are used as an index for the mask. Bits <3,2> are used as ; an index for field. ; MaskTbl DC.W $FFFF,$FFFF ; index 00 DC.W $FFFF,$0000 ; 01 DC.W $0000,$FFFF ; 10 DC.W $0000,$0000 ; 11 ;_______________________________________________________________________________________ <1.5> ; UpdateSRT - add or update an entry in the slot resource table ; InsertSRTRec - add a ROM or RAM sResource to the slot resource table ; ; UpdateSRT adds or updates an entry in the SRT based on spSlot, spId, and spExtDev. If ; the slot-id-extdev are found in the SRT, then the RefNum and IOReserved fields are ; updated. If the entry is not found, then a new record is added to the table with ; spSlot, spId, spExtDev, spRefNum, and spIOReserved. In addition to these fields, ; srrsRsrcPtr, srrType, and srrHWDev are updated by reading their values from the ; appropriate declaration ROM. Updates may be made to enabled sResources only. ; ; InsertSRTRec is similar to UpdateSRT except it uses the spsPointer field as an argument. ; If the spsPointer field is nil, then an sResource is added to the SRT if it exist ; in the sResource directory (based on slot-id-extdev) in the declaration ROM. If ; spsPointer is not nil, then assume we are adding a RAM sResource (not implemented yet). ; Also accept flags to indicate whether the sResource should be enabled or disabled. ; ; There are 5 cases to consider in the shared code : ; UpdateSRT : ; (1) Add a new sRsrc dir entry to SRT ; (5) Modify an existing SRT entry ; ; InsertSRT : ; (1) Add a new sRsrc dir entry to SRT (spsPointer == nil) ; (2) Add a new RAM sRsrc (not in sRsrc dir) to SRT (spsPointer == RAM addr) ; (3) Replace an SRT entry with a new RAM sRsrc (spsPointer == RAM addr) ; (4) Add a new RAM sRsrc (replacing one in sRsrc dir) to SRT (spsPointer == RAM addr) ; ; In case (3), when replacing an sResource, if there is a reference number ; (i.e. a driver) associated with the sResource we are replacing, then recalculate ; the dCtlDevBase field in the driver's DCE ; ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; For UpdateSRT and InsertSRT : ; spBlock : -> spSlot slot number ; -> spId sResource id ; -> spExtDev sResource external device id ; -> spRefNum reference number of driver for sResource ; -> spIOReserved reserved field ; ; In addition for InsertSRT only : ; -> spsPointer if nil then ROM sResource, else RAM sResource ; -> spParamData (formerly spStackPtr) 1 = disable, 0 = enable sResource ; EXPORT UpdateSRT,InsertSRT UpdateSRT MOVEQ #1,D0 ; reg D0 = 1 indicates UpdateSRT CLR.L spsPointer(A0) ; nil to simulate AddSRTRec call for add-new case CLR.L spParamData(A0) ; do not disable the sResource BRA.S ModifySRT InsertSRT MOVEQ #0,D0 ; reg D0 = 0 indicates InsertSRTRec ; Begin shared code for both UpdateSRT and InsertSRTRec ModifySRT MOVEM.L D1-D2/A1-A2,-(SP) ; save registers MOVE.L D0,D1 ; D1 = flag indicating Update or Insert MOVEA.L spsPointer(A0),A2 ; save reg A2 = spsPointer (ptr to RAM sRsrc or nil) MOVE.L spParamData(A0),D2 ; save enable/disable flag to set ; Search the SRT for the to see if the sResource already exists. CLR.L spParamData(A0) ; clear flags to FindSRTRec BSET.B #fall,spParamData+3(A0) ; set flag to look for all sRsrc's _FindSRTRec BEQ.S @Found ; sRsrc found - must be an update or a replacement ; ; At this point, the is not in the SRT Add the sRsrc to the SRT. ; MOVE.L A2,spsPointer(A0) ; restore ptr to RAM sRsrc or nil MOVE.L D2,spParamData(A0) ; restore spParamData = enable/disable flag slotjsr NewSRTEntry BRA.S @Done ; Doing update or replacement @Found MOVEA.L spsPointer(A0),A1 ; A1 = ptr to SRT entry, A2 = ptr to RAM sRsrc TST.W D1 ; are we executing Insert or Update SRT? BEQ.S @Replace ; doing Insert - replace SRT entry with a RAM sRsrc ; Doing an update on an existing entry . Check that the entry is enabled MOVE.W #smNoMoresRsrcs,D0 ; set error return in case BTST.B #srdisable,srrFlags+3(A1) ; is this an enabled or disabled entry ? BNE.S @Done ; error - trying to update a disabled entry MOVE.W spIOReserved(A0),srrIOReserved(A1) ; do update of existing entry MOVE.W spRefNum(A0),srrRefNum(A1) MOVEQ #0,D0 ; set good return status BRA.S @Done ; Replace an existing sRsrc entry in the SRT with a new RAM sRsrc. ; @Replace move.l a2,d0 ; is the ptr to the ram sRsrc nil ? <1.7> beq.s @Done ; yes - ignore this case - leave existing entry <1.7> MOVE.L A2,spsPointer(A0) ; pass ptr to RAM sResource MOVE.L D2,spParamData(A0) ; restore spParamData = enable/disable flag slotjsr InitEntry ; pass reg A1 = ptr SRT entry to replace ; BNE.S @Done ; some error @Done MOVEM.L (SP)+,D1-D2/A1-A2 RTS ;_______________________________________________________________________________________ <1.5> ; FindSRTRec - search the slot resource table for an sResource ; SearchSRT - search the SRT for visible sResource entries ; ; Search the slot resource table (SRT) for an sResource identified by the ; and fields. Optionally return a pointer either to the ; found SRT entry, or to the entry immediately following the found entry. ; ; FindSRTRec accepts a flag indicating whether the search sould include disabled ; (invisible) sResource entries in the SRT. SearchSRT is the original slot manager ; _sSearchSRT documented in Inside Mac vol 5, and it only searches visible entries. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spSlot slot number of sResource ; -> spId id of sResource ; -> spExtDev external device id of sResource ; -> spFlags bit 0 clear means return ptr for the given sResource ; set means return ptr for the following sResource ; <- spsPointer returns pointer to found or next entry in SRT. ; ; FindSRTRec only : ; -> spParamData input flag filed ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; bit 1 set = restrict search to single given slot ; clr = search all slots ; bit 2 set = search for next ; clr = search for given ; EXPORT SearchSRT,FindSRTRec SearchSRT CLR.L spParamData(A0) ; clear flag field for FindSRTRec BTST.B #fCkForNext,spFlags(A0) ; test for next search flag BEQ.S FindSRTRec ; not set - go to shared code BSET.B #fnext,spParamData+3(A0) ; transfer flag to new flag field FindSRTRec MOVEM.L D2-D4/A1-A3,-(SP) MOVEA.L sRsrcTblPtr,A1 ; get ptr to beginning of SRT MOVE.L spSlot(A0),D2 ; get to search for CLR.B D2 ; zero - not included in search key MOVEA.L A1,A2 ; init ptr to "found" entry MOVEA.L A1,A3 ; init ptr to a "next" entry MOVE.L MinusOne,D3 ; init a large "next" entry ; Loop and search each entry in the SRT blocks for the given . ; Reg A1 = ptr to current SRT entry ; A2 = ptr to "found" entry, D2 = "found" ; A3 = ptr to "next" SRT entry, D3 = "next" @Loop BSR GetSRTEntry ; return A1 = ptr to good entry BNE.S @NoMore ; no more good entries in the SRT - done MOVE.L srrSlot(A1),D4 ; get CLR.B D4 ; clear CMP.L D2,D4 ; are we looking for this one ? BGT.S @ChkNext ; no match - try "next" entry BLT.S @EndLoop ; no match and does not qualify for a "next" entry MOVEA.L A1,A2 ; matches - set ptr to "found" entry BTST.B #fnext,spParamData+3(A0) ; are we looking for the "next" entry ? BEQ.S @Done ; not looking for "next" - we are done BRA.S @EndLoop ; continue looking for the "next" one @ChkNext CMP.L D3,D4 ; check against current "next" entry BHI.S @EndLoop ; nope - greater than existing "next" MOVEA.L A1,A3 ; found new "next entry - update registers MOVE.L D4,D3 @EndLoop ADDA.W #SRTRecSize,A1 ; inc SRT entry ptr to next entry BRA.S @Loop ; continue looking ; Did not find the entry. Reg A3 = ptr to "next" valid SRT entry in the table. If we ; are set to search for the next sResource, then we are ok. @NoMore TST.L D3 ; did we ever update D3 ("next" ? BMI.S @Error ; nope - there is no "next" entry MOVEQ #0,D0 ; setup a good return MOVEA.L A3,A2 ; return ptr to "next" entry BTST.B #fnext,spParamData+3(A0) ; check "for next" bit BEQ.S @Error ; error - could not find specific entry ; A1 = valid ptr to NEXT entry. If the oneslot bit is set, then check if it is ; the same as the given slot number. @CheckSlot BTST.B #foneslot,spParamData+3(A0) ; restrict search to one slot ? BEQ.S @Done ; no - we are done MOVE.B spSlot(A0),D1 ; get D1 = given slot CMP.B srrSlot(A2),D1 ; still in same slot ? BEQ.S @Done ; yes - we are done @Error MOVE.W #smNoMoresRsrcs,D0 ; error - could not find entry in slot @Done MOVE.L A2,spsPointer(A0) ; return ptr to SRT entry MOVEM.L (SP)+,D2-D4/A1-A3 TST.W D0 RTS ;_______________________________________________________________________________________ <1.6> ; DeleteSRTRec - delete a given sResource entry from the SRT ; ; Search the slot resource table (SRT) for an sResource identified by the ; and fields. If found, then remove it from the table. ; This routine will delete an enabled or disabled entry from the SRT. ; ; Entries are removed by moving the last entry in the table to the deleted location. ; This keeps the SRT as a compacted (unordered) list. There is a pointer to the ; last entry stored in the slot manager globals. If after moving the last entry, the ; last block becomes free, then the block is freed. Because there is no back link ; pointer, the SRT must be travered from the beginning to the new last block, so that ; it's link pointer field may be nil-ed. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spSlot slot number of sResource ; -> spId id of sResource ; -> spExtDev external device id of sResource ; EXPORT DeleteSRTRec DeleteSRTRec MOVEM.L A0-A2,-(SP) ; Find the sResource entry in the SRT CLR.L spParamData(A0) ; clear flags to FindSRTRec BSET.B #fall,spParamData+3(A0) ; set flag to look for all sRsrc's _FindSRTRec BNE @Error ; sRsrc not found - done ; Mark the entry as being free (just in case) MOVEA.L spsPointer(A0),A1 ; A1 = ptr to found entry MOVE.W #srtfree,srrSlot(A1) ; place free tag at beginning of srrblock ; Compact the SRT by copying the last entry to the free space MOVEA.L ([sInfoPtr],lastSRTPtr),A2 ; A2 = ptr to last entry MOVE.W #SRTRecSize-1,D0 ; entry size (adjusted for dbra) @Loop MOVE.B (A2)+,(A1)+ ; copy last entry to freed entry DBRA D0,@Loop ; Determine whether the last block in the SRT chain is empty and can be freed. MOVEA.L ([sInfoPtr],lastSRTPtr),A2 ; get ptr to last entry again MOVE.W #srtfree,srrSlot(A2) ; place free tag at beginning of srrblock SUBQ.W #1,([sInfoPtr],srtCnt) ; dec total srt cnt MOVE.W ([sInfoPtr],srtCnt),D0 ; get new cnt DIVU.W #srtMaxEntries,D0 ; divide total cnt by num entries per blk AND.L #$FFFF0000,D0 ; D0 = , any remainder ? BNE.S @Good ; still entries left in last blk - done ; Last SRT block is empty - free the block. Traverse SRT to end to nil the link ptr. @Free MOVEA.L A2,A0 ; A0 = ptr to last SRT blk _DisposPtr ; free the block MOVEA.L sRsrcTblPtr,A1 ; get ptr to beginning of SRT @Loop1 ADDA.W #srtBlkSize,A1 ; inc to end of blk CMPA.L srtNext(A1),A2 ; found end of link ? BEQ.S @Found ; found new last blk MOVEA.L srtNext(A1),A1 ; advance to next blk BRA.S @Loop1 ; continue @Found CLR.L srtNext(A1) ; nil the link field MOVEA.L A1,A2 ; get ptr into A2 for the following shared code @Good SUB.W #SRTRecSize,A2 ; dec ptr to previous entry MOVE.L A2,([sInfoPtr],lastSRTPtr) ; update new last ptr MOVEQ #0,D0 ; a good return BRA.S @Done @Error MOVE.W #smRecNotFnd,D0 ; same error code as old slot manager @Done MOVEM.L (SP)+,A0-A2 RTS ;_______________________________________________________________________________________ <1.7> ; GetsRsrcInfo - get sResource information ; SlotRsrcInfo - get visible sResource information ; ; Given an sResource's , find the sResource's SRT entry and return ; some of the information stored in the SRT entry. ; ; Input : reg A0 = ptr to spBlock ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot number ; -> spId sResource id ; -> spExtDev external device id ; <- spHWDev hardware device id (if applicable) ; <- spsPointer pointer sResource list (*****different than old slot manager) ; <- spRefNum driver reference number (if applicable) ; <- spIOReserved ; <- spCategory sType fields ; <- spCType ; <- spDrvrSW ; <- spDrvrHW ; ; For GetsRsrcInfo only : ; -> spParamData input flag filed ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; ; <- spParamData state of sResource: 0=enabled, 1=disabled ; EXPORT SlotRsrcInfo,GetsRsrcInfo SlotRsrcInfo CLR.L spParamData(A0) ; clear flag field GetsRsrcInfo MOVE.L A1,-(SP) _FindSRTRec ; search for the SRT entry BNE.S @Done ; error - sRsrc not found MOVEA.L spsPointer(A0),A1 ; pass A1 = ptr to SRT entry slotjsr SrToSpBlock ; fill in spBlock with srrBlock values bra.s @Done @Error move.w #smRecNotFnd,d0 ; set compatible error return @Done MOVEA.L (SP)+,A1 RTS ;_______________________________________________________________________________________ ; SetsRsrcState - enable or disable an sResource ; ; Search the slot resource table (SRT) for a given sResource identified by ; and fields. Set the flag in the SRT record to enable or ; disable the sResource. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spSlot slot number of sResource ; -> spId id of sResource ; -> spExtDev external device id of sResource ; -> spParamData 0 = enable, 1 = disable ; EXPORT SetsRsrcState ; <1.5> SetsRsrcState MOVEM.L D1/A1,-(SP) MOVE.L spParamData(A0),D1 ; save enable/disable state to set CLR.L spParamData(A0) ; clear flag field BSET.B #fall,spParamData+3(A0) ; search all sResources _FindSRTRec BNE.S @Done ; sRsrc not found MOVEA.L spsPointer(A0),A1 ; get A1 = ptr to SRT entry BCLR.B #srDisable,srrFlags+3(A1) ; assume enabling the sResource TST.B D1 ; enabling or disabling ? BEQ.S @Done ; enabling - we already did, so done BSET.B #srDisable,srrFlags+3(A1) ; disable the sResource MOVEQ #0,D0 ; set good return @Done MOVE.L D1,spParamData(A0) ; restore param data field MOVEM.L (SP)+,D1/A1 TST.W D0 RTS ;_______________________________________________________________________________________ <1.5> ; pNewSRTEntry - Add a new record to the SRT ; ; Add a new record entry to the slot resource table (SRT). Insert the entry to the ; proper place in the table. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spsPointer ptr to RAM sRsrc, or nil ; -> spParamData enable/disable flag ; EXPORT pNewSRTEntry pNewSRTEntry MOVEM.L D1/A1-A2,-(SP) MOVE.L spsPointer(A0),D0 ; test if there is a ptr to a RAM sRsrc BNE.S @FindFree ; yes - add the SRT entry ; Find the sResource in the ROM sResource directory, based on the . ; ***** Under the old slot mgr, if the sRsrc could not be found, it was not an error. MOVE.L spParamData(A0),D1 ; save enable/disable flags _sFindsInfoRecPtr ; get ptr to sinfo record MOVEA.L spResult(A0),A1 ; A1 = ptr to sInfo record MOVE.L siDirPtr(A1),spsPointer(A0) ; set ptr to ROM directory _sFindStruct ; search the ROM directory BNE.S @Done ; can't find it - error (***** different from old slot mgr) MOVE.L D1,spParamData(A0) ; restore flag ; Find a free entry in the SRT. If there is no free space left, then allocate and ; link a new SRT block. @FindFree MOVEA.L ([sInfoPtr],lastSRTPtr),A1 ; A1 = ptr to last entry in SRT <1.6> @Loop CMPI.W #srtfree,srrSlot(A1) ; free block ? BEQ.S @AddEntry ; found a free SRT entry CMPI.W #srtend,srrSlot(A1) ; end of current block ? BEQ.S @NewBlock ; need to alloc a new blk <1.6> ADDA.W #SRTRecSize,A1 BRA.S @Loop ; Allocate a new SRT block and link it in @NewBlock MOVEA.L A1,A2 ; save ptr to current blk slotjsr AllocSRTBlk ; return A1 = ptr to new blk BNE.S @Done ; memory error MOVE.L A1,srtNext(A2) ; update link field ; Initialize the new SRT entry - A1 = ptr to free SRT entry @AddEntry slotjsr InitEntry BNE.S @Done ; some error <1.6> ADDQ.W #1,([sInfoPtr],srtCnt) ; inc SRT count <1.6> MOVE.L A1,([sInfoPtr],lastSRTPtr) ; save ptr to last entry in SRT <1.6> @Done MOVEM.L (SP)+,D1/A1-A2 ; restore regs RTS ;_______________________________________________________________________________________ ; pInitEntry - init an SRT entry ; ; Initialize and fill in the fields of a slot resource table entry. ; ; Input : reg A0 = ptr to spBlock ; A1 = ptr to SRT entry to initialize ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spSlot slot number ; -> spId sResource id ; -> spExtDev external device id ; -> spRefNum reference number or nil ; -> spIOReserved reserved value, or nil ; -> spsPointer pointer to sResource ; -> spParamData enable/disable flag ; EXPORT pInitEntry pInitEntry MOVEM.L D1/A2,-(SP) ; save regs SUBA.W #SRSize,SP ; alloc size to read sRsrc sType field MOVEA.L SP,A2 ; save A2 = ptr to buffer ; Fill in the fields of a new SRT entry MOVE.B spSlot(A0),srrSlot(A1) ; slot number MOVE.B spId(A0),srrId(A1) ; sRsrc id MOVE.B spExtDev(A0),srrExtDev(A1) ; external device id CLR.B srrHWDev(A1) ; clear hardware device id MOVE.W spRefNum(A0),srrRefNum(A1) ; driver reference number MOVE.W spIOReserved(A0),srrIOReserved(A1) ; IO reserved field (good for nothin?) MOVE.L spsPointer(A0),srrsRsrcPtr(A1) ; set the ptr to the RAM or ROM sRsrc CLR.L srrFlags(A1) ; clear flag field MOVE.L spParamData(A0),D0 ; test state of enable/disable value BEQ.S @ReadStuff ; zero - sRsrc is marked as enabled BSET.B #srDisable,srrFlags+3(A1) ; set flag to indicate disabled ; Read the hardware sRsrc id @ReadStuff MOVE.B #sRsrcHWDevId,spId(A0) ; get hardware id (if present) _sReadByte ; no error if not present BNE.S @Continue MOVE.B spResult+3(A0),srrHWDev(A1) ; only a byte value ; Find and read the sRsrc type field @Continue MOVE.B #sRsrcType,spId(A0) ; get ptr to sRsrc type _sFindStruct BNE.S @Error ; error - sRsrc type field is required MOVE.L #SRSize,spSize(A0) ; set size to read MOVE.L A2,spResult(A0) ; set buffer ptr _sReadStruct BNE.S @Error ; error - found but can't read ? MOVE.L sCategory(A2),srrCategory(A1) ; copy MOVE.L sDrvrSw(A2),srrDrvrSw(A1) ; copy ; If there is a valid reference number, then find the DCE and calculate the dCtlDevBase <1.5> MOVEQ #0,D0 ; set a good return MOVE.W spRefNum(A0),D1 ; get ref num BEQ.S @Done ; no ref num - done MOVE.W #rfNumErr,D0 ; set a bad return NOT.W D1 ; test for valid ref number BMI.S @Error ; invalid - error MOVE.L ([UTableBase],D1.W*4),A2 ; DCE handle MOVE.L (A2),A2 ; dereference handle ; Read a 24 or 32 bit base address from the sResource <2.0> ; Fixes a bug when calling _InsertSRTRec, inserting a ROM sRsrc with a valid ; refnum, pInitEntry is called. pInitEntry calls _sFindDevBase to calc a base ; addr to place in the DCE. The bug is _sFindDevBase is called with a bad ; sRsrc id. The fix is one line to restore the spId before calling ; _sFindDevBase. move.b srrId(a1),spId(a0) ; set spId of sRsrc to get base addr (the fix) _sFindDevBase ; get base address BNE.S @Error MOVE.L spResult(A0),dCtlDevBase(A2) ; set the dCtlDevBase MOVE.B srrId(A1),dCtlSlotId(A2) ; update sResource id <1.6> MOVE.B srrExtDev(A1),dCtlExtDev(A2) ; update the external device id <1.6> BRA.S @Done ; Some error occurred - mark the SRT entry free again @Error MOVE.W #srtfree,srrSlot(A1) @Done MOVE.L srrsRsrcPtr(A1),spsPointer(A0) ; restore ptr to sRsrc ADDA.W #SRSize,SP ; free sRsrc type buffer MOVEM.L (SP)+,D1/A2 ; restore regs TST.W D0 ; set CCR RTS ;_______________________________________________________________________________________ <2.0> ; pAllocSRTBlk - allocate and initialize an SRT block ; ; Allocate an SRT block. Initialize all the SRT entries to free. ; ; Input : none ; ; Output : reg A1 = ptr to new SRT block ; D0 = status, 0=ok CCR reflects status ; EXPORT pAllocSRTBlk pAllocSRTBlk move.l a0,-(sp) move.l #srtBlkSize+srtLinkSize,d0 ; d0 = size to allocate _NewPtr ,Sys,Clear ; allocate block bne.s @Done movea.l a0,a1 ; save copy of ptr to SRT block for the return move.w #srtMaxEntries-1,d0 ; number of entries in SRT (adjusted for dbra) @Loop move.w #srtfree,srrSlot(a0) ; mark entries as free adda.w #SRTRecSize,a0 ; inc to next entry dbra d0,@Loop move.w #srtend,srtMarker(a0) ; indicate link and end of block moveq #noErr,d0 ; good return status @Done movea.l (sp)+,a0 rts ;_______________________________________________________________________________________ ; GetSRTEntry - return a pointer to the next visible SRT entry ; ; Given a pointer to an entry in an SRT block, return that pointer if the SRT entry ; is visible. If it is not visible, or if the pointer is to the end of the SRT ; block, increment and return a pointer to the next visible SRT entry. Walk down ; the linked SRT blocks if necessary. ; ; Input : reg A0 = ptr to spBlock ; A1 = ptr to SRT entry to get or start search from ; ; Output : reg A1 = ptr to visible SRT entry ; D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spParamData input flag filled ; bit 0 set = include disabled sResources in search ; clr = ignore disabled sResources ; Export GetSRTEntry GetSRTEntry MOVEM.L D1-D2/A0,-(SP) @Loop MOVE.W srrSlot(A1),D1 ; get BMI.S @ChkEnd ; escape flag - check for end of block BTST.B #fall,spParamData+3(A0) ; search includes disabled sResource entries ? BNE.S @Good ; yes - return whatever entry we have BTST.B #srdisable,srrFlags+3(A1) ; is this entry enabled ? BEQ.S @Good ; yes - return ptr to good entry BRA.S @EndLoop ; otherwise inc to next entry and continue ; Entry has escape flag (srrSlot == $FF). Check for end of block @ChkEnd CMP.W #srtEnd,D1 ; end of list ? BNE.S @EndLoop TST.L srtNext(A1) ; end of block - any more srt blks ? BEQ.S @NoMore ; end or SRT MOVEA.L srtNext(A1),A1 ; point to top of next block BRA.S @Loop ; continue looking @EndLoop ADDA.W #SRTRecSize,A1 ; inc to next entry BRA.S @Loop @NoMore MOVE.W #smRecNotFnd,D0 ; no good entries BRA.S @Done @Good MOVEQ #0,D0 ; set good return @Done MOVEM.L (SP)+,D1-D2/A0 RTS ;_______________________________________________________________________________________ <1.3> ; pSrToSpBlock - copy srBlock info to spBlock ; ; ; ; Input : reg A0 = ptr to spBlock ; A1 = ptr to srBlock ; ; Output : none ; ; spBlock : <- spSlot slot to start looking in ; <- spId id to start looking from ; <- spExtDev external device identifier ; <- spHWDev hardware device id (if applicable) ; <- spsPointer pointer sResource list ; <- spRefNum driver reference number (if applicable) ; <- spIOReserved ; <- spCategory sType fields ; <- spCType ; <- spDrvrSW ; <- spDrvrHW ; <- spParamData 1 = sRsrc is disabled, 0 = enabled (*****different from old slotmgr) ; EXPORT pSrToSpBlock pSrToSpBlock MOVE.B srrSlot(A1),spSlot(A0) MOVE.B srrId(A1),spId(A0) MOVE.B srrExtDev(A1),spExtDev(A0) MOVE.B srrHWDev(A1),spHWDev(A0) MOVE.W srrRefNum(A1),spRefNum(A0) MOVE.W srrIOReserved(A1),spIOReserved(A0) MOVE.W srrCategory(A1),spCategory(A0) MOVE.W srrCType(A1),spCType(A0) MOVE.W srrDrvrSw(A1),spDrvrSW(A0) MOVE.W srrDrvrHw(A1),spDrvrHW(A0) MOVE.L srrsRsrcPtr(A1),spsPointer(A0) ; return ptr to sRsrc list CLR.L spParamData(A0) ; clear return flags field BTST.B #srdisable,srrFlags+3(A1) ; test disable flag BEQ.S @Done ; not disabled - return zero MOVE.L #1,spParamData(A0) ; disabled - return 1 @Done RTS ;_______________________________________________________________________________________ ; CalcStep - calculate the byte lane's step register value ; ; The step register contains the value to add to a pointer to a declaration ROM, to ; increment to the next consecutive byte or id field. NuBus cards are not required to ; support all 4 byte lanes, so the address increment value between consecutive bytes ; may be greater than 1 (see Designing Cards and Driver's manual for more detail on ; bytelanes). ; ; The step register is a long, having the format of , ; where each increment value is a byte. The increment values indicate from the first ; byte lane supported, how much to increment to the next consecutive byte or id field. ; The step register is used as a rotating shift register, so the increment values may ; repeat. For example, if only 1 byte lane where supported, then the step register ; value would be <04><04><04><04>. If all 4 byte lanes are supported, then the step ; register would be <01><01><01><01>. For 2 or 3 byte lanes, the step register value ; depends on the byte lanes supported. ; ; When used for accessing consecutive bytes, the step register the low byte is added ; to the address to get the next byte. Then the step register is rotated left on byte ; in preparation for the next byte access. When accessing consecutive id's, only the ; low byte is needed as the increment value. No rotation is needed. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : -> spsPointer NuBus address to calc step value for ; -> spByteLanes byte lane for slot ; -> spFlags if bit 5 is set, then calc for consecutive bytes, else id's ; <- spResult step value ; CalcStep PROC EXPORT WITH spBlock MOVEM.L D1-D3/A1,-(SP) MOVE.W #smBadsPtrErr,D0 ; assume an error CLR.W D1 ; clear for later CLR.W D2 ; clear for later MOVE.B spsPointer+3(A0),D1 ; get low byte of NuBus address AND.L #$03,D1 ; get low 2 bits = using which byte lane MOVE.B spByteLanes(A0),D2 ; reg D2 = byte lanes supported for card BTST.L D1,D2 ; using a valid byte lane ? BEQ.S @Error ; a bad pointer for this slot MOVE.L D2,D3 ; get copy D3 = byte lanes for slot ASL.W #2,D3 ; adjust index to long entries in table BTST.B #fConsecBytes,spFlags(A0) ; calculating bytes or id's ? BEQ.S @Ids ; do id's ; Do table lookup to get step register value for consecutive bytes ; reg D3 = byte lanes for slot * 4, D1 = byte lane spsPointer is occupying (used to rotate step value) LEA ByteTable,A1 ; reg A1 = ptr to byte access table MOVE.L 0(A1,D3.W),D2 ; reg D2 = step value MULU.W #8,D1 ; calc which step value current byte lane is on ROR.L D1,D2 ; D2 = step value corrected to current byte lane MOVE.L D2,spResult(A0) BRA.S @Done ; Do table lookup to get step register value for consecutive id's ; reg D2 = byte lanes for slot, D1 = byte lane spsPointer is occupying @Ids LEA IdTable,A1 ; reg A1 = addr of id access table MOVE.L 0(A1,D3.W),spResult(A0) ; return step value - no rotation needed BPL.S @Done ; if negative, then calc for 3 byte lanes ; Card supports three byte lanes. Must index into an auxilary table. There are 4 valid ; and 1 invalid entry in the table (total of 5). Each entry has the step value for the ; slot's byte lane configuration, a different step value depending on which byte lane ; the spsPointer occupies. LEA ThreeByteTbl,A1 ; get addr of auxilary table for 3 byte lanes AND.B #7,D2 ; use low 3 bits for indexing into table SUB.B #3,D2 ; adjust index for table ASL.L #4,D2 ; multiply by 16 bytes (size of each entry) ADDA.L D1,A1 ; add in current byte lane offset MOVE.L 0(A1,D2.W),spResult(A0) ; get step value for 3 byte lane support @Done CLR.W D0 ; set good result @Error MOVEM.L (SP)+,D1-D3/A1 RTS ;_______________________________________________________________________________________ ; Byte lane translation tables ; ; ByteTable, corresponds to consecutive bytes. IdTable, corresponds to consecutive ; id fields. ThreeByteTbl, corresponds to consecutive id fields on cards which support ; three byte lanes. Each entry is 4 longs. These byte lanes have their entries as -1 ; in IdTable. ; ; step values byte lanes ; ----------- ---------- ByteTable DC.L $0 ; no byte lane indexed at 0 DC.L $04040404 ; 0 DC.L $04040404 ; 1 DC.L $03010301 ; 0,1 DC.L $04040404 ; 2 DC.L $02020202 ; 0,2 DC.L $03010301 ; 1,2 DC.L $00020101 ; 0,1,2 DC.L $04040404 ; 3 DC.L $01030103 ; 0,3 DC.L $02020202 ; 1,3 DC.L $00010201 ; 0,1,3 DC.L $03010301 ; 2,3 DC.L $00010102 ; 0,2,3 DC.L $00020101 ; 1,2,3 DC.L $01010101 ; 0,1,2,3 IdTable DC.L $0 ; no byte lane indexed at 0 DC.L $10101010 ; 0 DC.L $10101010 ; 1 DC.L $08080808 ; 0,1 DC.L $10101010 ; 2 DC.L $08080808 ; 0,2 DC.L $08080808 ; 1,2 DC.L $FFFFFFFF ; 0,1,2 DC.L $10101010 ; 3 DC.L $08080808 ; 0,3 DC.L $08080808 ; 1,3 DC.L $FFFFFFFF ; 0,1,3 DC.L $08080808 ; 2,3 DC.L $FFFFFFFF ; 0,2,3 DC.L $FFFFFFFF ; 1,2,3 DC.L $04040404 ; 0,1,2,3 ThreeByteTbl DC.L $05050505 ; 0,1,3 DC.L $06060606 ; DC.L $0 ; DC.L $05050505 ; DC.L $0 ; empty DC.L $0 ; DC.L $0 ; DC.L $0 ; DC.L $06060606 ; 0,2,3 DC.L $0 ; DC.L $05050505 ; DC.L $05050505 ; DC.L $0 ; 1,2,3 DC.L $05050505 ; DC.L $05050505 ; DC.L $06060606 ; DC.L $05050505 ; 0,1,2 DC.L $05050505 ; DC.L $06060606 ; DC.L $0 ; ;_______________________________________________________________________________________ ; OffsetData - read an offset/data field ; ; Read the offset/data field identified by spId, in the list pointed to by spsPointer. ; The offset/data field is the 3 byte field following the id in a list entry : ; . This routine may be used for general data access of a list. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : <-> spsPointer On entry is ptr to list to search, on exit is ptr ; to id in list. This can be used to calculate a new ; pointer offset by the value of the offset/data field. ; -> spId Id in list to search for ; <- spOffsetData the value of the offset data field ; <- spByteLanes byte lane for slot ; OffsetData PROC EXPORT WITH spBlock,sInfoRecord MOVEM.L D1-D2/A1,-(SP) MOVE.B spSlot(A0),-(SP) ; save slot field (if any) MOVE.W #smBadRefId,D0 ; asume an error CMPI.B #$FF,spId(A0) ; is id less than $FF ? beq @Done ; no - id out of range ; Get the sInfo record for the slot. Derive the slot number from the spsPointer. ; If the spsPointer is to a RAM list, then slot number gets translated to slot 0. _sPtrToSlot ; convert to slot number bne @Done _sFindsInfoRecPtr ; get ptr to sInfo record and status <1.6> MOVE.L spResult(A0),A1 ; reg A1 = ptr to sInfo record move.w siInitStatusA(a1),d0 ; test slot bmi.s @Done ; bad slot - skip it ; Calculate the step value to consecutive bytes MOVE.B siCPUByteLanes(A1),spByteLanes(A0) ; get byte lane field from sInfo rec BSET.B #fConsecBytes,spFlags(A0) ; set flag for consecutive bytes _sCalcStep ; calc step value for spsPointer bne.s @Done ; Loop and read the fields (a long) from the list. MOVE.L spResult(A0),spParamData(A0) ; step value in spParamData MOVEQ #0,D1 ; clear for last id read @Loop MOVE.B D1,D2 ; save D2 = last id read MOVE.L spsPointer(A0),A1 ; save reg A1 = ptr to current id slotjsr Read4Bytes ; read bne.s @Done ; some error MOVE.B spResult(A0),D1 ; reg D1 = MOVE.W #smBadsList,D0 ; assume out of order error CMP.B D2,D1 ; check for ascending order bcs.s @Done ; out of order MOVE.W #smBadRefId,D0 ; assume not found CMP.B #$FF,D1 ; end of list ? beq.s @Done ; id not found CMP.B spId(A0),D1 ; found id ? BNE.S @Loop ; not found - continue ; Found id - return offset/data value MOVE.L spResult(A0),D0 ; get AND.L #$00FFFFFF,D0 ; mask off id MOVE.L D0,spOffsetData(A0) ; set return offset/data field MOVE.L A1,spsPointer(A0) ; set ptr to id in list moveq #noErr,d0 ; set a good return @Done MOVE.B (SP)+,spSlot(A0) ; restore save slot number MOVEM.L (SP)+,D1-D2/A1 TST.W D0 RTS ;_______________________________________________________________________________________ <2.0> ; ReadPBSize - read the physical block size field of an sBlock ; ; Search a list pointed to by spsPointer for the id spId. Use the offset/data field ; of the id to calculate a pointer to an sBlock. Return the physical block size of ; the sBlock. Also return the pointer to the sBlock after the size field. Optionally ; return a long instead of the physical block size (PBSize is masked to 3 bytes). ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : <-> spsPointer On entry is ptr to list to search, on exit is ptr ; to sBlock. ; -> spId Id in list to search for ; -> spFlags bit 1 set means check high byte of size for zero ; <- spSize physical block size field of sBlock ; <- spByteLanes byte lane for slot ; ; Called : trap dispatcher, jsr ; ReadPBSize Proc Export With spBlock,sInfoRecord movem.l d1/a1,-(sp) move.b spSlot(a0),-(sp) ; save slot field (if any) ; Search the list pointed to by spsPointer for the spId. Use the offset/data ; field to calculate a pointer to the sBlock. _sFindStruct ; return new spsPointer bne.s @Done ; Read the PBSize field pointed to by spsPointer. Increment spsPointer to after the ; size field. _sPtrToSlot ; get slot number bne.s @Done _sFindsInfoRecPtr ; get ptr to sInfo record and status <1.6> movea.l spResult(a0),a1 ; reg a1 = ptr to sInfo record move.w siInitStatusA(a1),d0 ; test slot bmi.s @Done ; bad slot - skip it ; Calculate the step value to consecutive bytes move.b siCPUByteLanes(a1),spByteLanes(a0) ; get byte lane field from sInfo rec bset.b #fConsecBytes,spFlags(a0) ; set flag for consecutive bytes _sCalcStep ; calc step value for spsPointer bne.s @Done move.l spResult(a0),spParamData(a0) ; step value in spParamData slotjsr Read4Bytes ; read PBSize field bne.s @Done ; Optionally check the PBSize field to make sure that the high byte (a reserved field), ; is zero. move.l spResult(a0),spSize(a0) ; move pbsize to size field moveq #noErr,d0 ; assume a good return btst.b #fCkReserved,spFlags(a0) ; check reserved field ? beq.s @Done ; no - we are done move.b spResult(a0),d1 ; d1 = high byte of PBSize field beq.s @Done ; it's ok move.w #smReservedErr,d0 ; not zero - log an error @Done move.b (sp)+,spSlot(a0) ; restore save slot number movem.l (sp)+,d1/a1 tst.w d0 rts ;_______________________________________________________________________________________ <2.0> ; pRead4Bytes - read 4 bytes from NuBus ; ; Utility routine to read 4 bytes from NuBus. This differs from ReadLong(), in that ; it doesn't do a lot of the endless slot manager checking. ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; ; spBlock : <-> spPointer address of 4 bytes to read - on exit, ptr to next long ; -> spParamData consecutive byte step value ; -> spSlot slot number ; <- spResult 4 bytes read ; pRead4Bytes PROC EXPORT WITH spBlock,sInfoRecord movem.l d1-d4/a1-a2,-(sp) ; Setup for accessing NuBus MOVE.L spParamData(A0),D2 ; get step value MOVEA.L spsPointer(A0),A1 ; reg A1 = ptr to read bytes from MOVEQ #3,D3 ; D3 = loop cntr MOVEQ #0,D4 ; clear for temp reg for macro slotjsr InstallBus ; switch to 32bit mode and new bus exception lea @Done,a2 ; set addr to jump to if bus error move.w #smUnExBusErr,d0 ; assume unexpected bus error @Loop asl.l #8,d1 ; shift previously read value move.b (a1),d1 ; NUBUS READ - read byte sNextStep d2,d4,a1 ; macro to inc ptr to next byte dbra d3,@Loop ; continue move.l d1,spResult(a0) ; set result to 4 bytes read MOVE.L A1,spsPointer(A0) ; update incremented ptr MOVEQ #noErr,D0 ; done - set good return @Done slotjsr RestoreBus ; restore mmu mode and bus exception movem.l (sp)+,d1-d4/a1-a2 RTS ;_______________________________________________________________________________________ <4> ; GetBoard - get ptr to board sResource ; ; Given a slot number - return a pointer to the board sResource and sInfo record ; ; Input : reg A0 = ptr to spBlock ; ; Output : reg D0 = status, 0=ok CCR reflects status ; A0 = ptr to spBlock ; ; spBlock : -> spSlot slot number ; -> spId sRsrc id to search from <8> ; <- spsPointer ptr to board sResource ; <- spResult ptr to sInfo record ; Export pGetBoard pGetBoard move.l a1,-(sp) _sFindsInfoRecPtr ; get the sInfo record ptr movea.l spResult(a0),a1 ; save a1 = ptr to sInfo record ; Get the board sResource move.l #((CatBoard<<16)++TypBoard),spCategory(a0) ; set category and type fields clr.l spDrvrSW(a0) ; no drvrSW and drvrHW fields clr.b spTBMask(a0) ; no masking clr.b spExtDev(a0) ; clear external device id field (not a device) clr.l spParamData(a0) ; clear flag field IF NOT forROM THEN ; rb bset.b #fall,spParamData+3(a0) ; search all sResources bset.b #foneslot,spParamData+3(a0) ; search in only one slot ELSE ; rb ori.b #(1< rb search all sRsrc's in one slot <4> ENDIF ; rb _GetTypesRsrc ; return ptr to sResource beq.s @Done move.w #smNoBoardsRsrc,d0 ; no board sResource @Done move.l a1,spResult(a0) ; restore spResult to sInfo ptr movea.l (sp)+,a1 tst.w d0 rts ;_______________________________________________________________________________________ ; pBusException - nubus bus error exception handler ; ; This is the slot manager's replacement bus error exception handler. It is designed ; to detect faulted Nubus address data read bus cycles. It is NOT designed to handle ; data write or read-modify-write cycles, or instruction fetch faults. These exceptions ; are transfered to the old bus exception handler. ; ; Upon an exception, the stack frame type is verified for as being one this routine is ; able to handle (in this case, a long bus cycle stack frame only). The SSW is check ; for a data read cycle fault ONLY. If the fault address is a NuBus address (32 bit ; address), then the exception stack frame is pop-ed and the exception return address ; in reg a2 is jumped to. ; ; Input : reg a2 address to return from exception when a bus error occurs ; Output : ccr set to value in reg d0 ; pBusException Proc Export Export pInstallBus,pRestoreBus stackframe RECORD 0 savereg DS.L 1 ; saved register on stack statusreg DS.W 1 programCnt DS.L 1 type DS.B 1 ; format frame type fill DS.B 3 ; filler ssw DS.W 1 ; special status register fill2 DS.L 1 ; filler DFAddr DS.L 1 ; data cycle fault address remainder DS.B 72-8 ; remainder of stack frame minus the short frame shortSR ds.w 1 ; beginning of short stack frame definition shortPC ds.l 1 ; new pc for short frame shortvers ds.w 1 ; version and vector offset ENDR WITH stackframe,slotGlobals ; Verify that this is a faulted NuBus read data cycle move.l d0,-(sp) ; save working register move.w ssw(sp),d0 ; get special status register and.w #$F1C0,d0 ; mask FC FB RC RB DF RM RW cmp.w #$0140,d0 ; DF and RW bit set only ? bne.s @RealBusEx ; can't handle this case - pass it on move.b type(sp),d0 ; get format of stack frame for long frame lsr.b #4,d0 ; look at high nibble cmp.b #$0B,d0 ; long bus exception frame ? bne.s @RealBusEx ; transfer to real bus exception handler move.b DFAddr(sp),d0 ; get high byte of data fault cycle address cmp.b #majorSpace,d0 ; in super slot space ($60-$E0) ? blo.s @RealBusEx ; not in slot address space cmp.b #$FF,d0 ; in minor slot space range ? beq.s @RealBusEx ; not in minor slot space cmp.b #$F0,d0 ; in minor slot space range ? beq.s @RealBusEx ; not in minor space $F1 - $FE ; Have verified that a NuBus read data access caused the bus error. Need to modify the ; stack frame to return to the address in register a2. Accomplish this by creating a new ; short stack frame and setting a new PC. The long bus exception PC is popped off leaving ; a short exception frame. Cannot just modify the PC in the long frame to return to a new ; address (this doesn't work). move.l (sp),d0 ; restore reg d0 move.l a2,shortPC(sp) ; set new return address in short frame move.w statusreg(sp),shortSR(sp) ; move the SR clr.w shortvers(sp) ; clear frame type and vector offset adda.w #shortSR,sp ; pop long frame leaving a short frame rte ; The bus exception was not caused by a read to NuBus - pass the exception to the ; real bus exception handler. @RealBusEx move.l (sp)+,d0 ; restore reg D0 jmp ([sInfoPtr],sysBusExcptn) ; jump to bus exception vector ;_______________________________________________________________________________________ <7> ; pInstallBus - install the slot manager's bus exception vector ; ; Switch to 32 bit mode and replace the system bus exception handler with the slot ; manager's exception handler. Return the saved mmu state in reg D0. Installing ; the slot manager's vector is based on a use count in the slot mgr globals. If the ; count is zero, then save the system vector and install the new vector. If the count ; is not zero, then assume some embedded slot mgr routine has already replaced the ; vector. In that case, just increment the count. This routine may be called at ; interrupt level. ; ; Input : none ; Output : none ; ; Destroys: d0 ; pInstallBus move.w sr,-(sp) ; Save current interrupt level. ori.w #HiIntMask,sr ; disable interrupts moveq #True32B,d0 _SwapMMUMode ; change to 32 bit mode move.b d0,([sInfoPtr],entryMMUMode) ; save old mmu state move.l BusErrVct,([sInfoPtr],sysBusExcptn) ; save system bus vector in globals move.l ([SDMJmpTblPtr],BusException*4),BusErrVct ; replace with slot mgr vector move.w (SP)+,SR ; restore interrupt state rts ;_______________________________________________________________________________________ <7> ; pRestoreBus - restore the system bus exception vector ; ; Restore the mmu state and the system's bus exception vector. If the bus exception ; use count is incremented to zero, then there is no slot mgr routine still using ; the exception vector, so restore the system's vector (saved in the slot mgr globals). ; If the count is non-zero, then do nothing. This routine may be called at interrupt ; level. ; ; Input : none ; Output : none ; ; Preserves all registers ; pRestoreBus move.l d0,-(sp) ; save reg move.w sr,-(sp) ; Save current interrupt level. ori.w #HiIntMask,sr ; disable interrupts move.b ([sInfoPtr],entryMMUMode),d0 ; get saved mmu mode _SwapMMUMode ; restore mmu mode move.l ([sInfoPtr],sysBusExcptn),BusErrVct ; restore system exception vector move.w (sp)+,sr ; restore interrupt state move.l (sp)+,d0 ; restore reg rts ENDWITH ; { stackframe,slotGlobals } <5> Endp ; must have endp for RAM builds End