Clean QuickDraw lurkers

Only three monolithic chunks of code to go!
This commit is contained in:
Elliot Nunn
2017-10-09 15:46:40 +08:00
parent cf23aad670
commit b295a57713
15 changed files with 79 additions and 89 deletions

View File

@@ -202,7 +202,8 @@ processAppSpec EQU 56
MACRO MACRO
_GetFrontProcess _GetFrontProcess
PEA $FFFFFFFF MOVEQ.L #$FFFFFFFF,D0
MOVE.L D0,-(SP)
MOVE.W #$39,-(SP) MOVE.W #$39,-(SP)
_OSDispatch _OSDispatch
ENDM ENDM

View File

@@ -266,7 +266,7 @@ PMFlag EQU $8000 ; flag to say it's a new pixMap
cPortFlag EQU $C000 ; isPixMap+isCPort cPortFlag EQU $C000 ; isPixMap+isCPort
pixVersion EQU $0000 ; isPixMap pixVersion EQU $0000 ; isPixMap
qdStackXtra EQU $0640 ; stack space left for interrupts <1.4> BAL qdStackXtra EQU $0800 ; stack space left for interrupts <1.4> BAL
isPixMap EQU 15 ; for testing high bit of pRowbytes isPixMap EQU 15 ; for testing high bit of pRowbytes
isCPort EQU 14 ; indicates that "bitmap" belongs to port isCPort EQU 14 ; indicates that "bitmap" belongs to port
@@ -376,7 +376,7 @@ CCSTATEREGS EQU CCDEPTH+2 ;[16 BYTES] STATE INFO OF SAVED DATA
CCBYTES EQU CCSTATEREGS+16 ;[WORD] ROWBYTES OF EXPANDED DATA CCBYTES EQU CCSTATEREGS+16 ;[WORD] ROWBYTES OF EXPANDED DATA
CCMAXDEPTH EQU CCBYTES+2 ;[WORD] MAXIMUM SCREEN DEPTH CCMAXDEPTH EQU CCBYTES+2 ;[WORD] MAXIMUM SCREEN DEPTH
CCSAVEREC EQU CCMAXDEPTH+2 ;SIZE OF CURSOR SAVE AREA CCSAVEREC EQU CCMAXDEPTH+2+8 ;SIZE OF CURSOR SAVE AREA
; Font Manager low mem ; Font Manager low mem
; ;

View File

@@ -1741,7 +1741,7 @@ DSTRECT EQU MASKRECT-4 ;long, addr of Rect
MODE EQU DSTRECT-2 ;WORD MODE EQU DSTRECT-2 ;WORD
MASKRGN EQU MODE-4 ;LONG, RGNHANDLE MASKRGN EQU MODE-4 ;LONG, RGNHANDLE
VARSIZE EQU 0 VARSIZE EQU -4
share LINK A6,#VARSIZE ;ALLOCATE STACK FRAME share LINK A6,#VARSIZE ;ALLOCATE STACK FRAME
MOVEM.L D3-D7/A2-A4,-(SP) ;SAVE WORK REGISTERS FOR DEVLOOP MOVEM.L D3-D7/A2-A4,-(SP) ;SAVE WORK REGISTERS FOR DEVLOOP
@@ -1774,7 +1774,7 @@ share LINK A6,#VARSIZE ;ALLOCATE STACK FRAME
PEA.L MASKRECT(A6) PEA.L MASKRECT(A6)
MOVE.L D3, -(SP) MOVE.L D3, -(SP)
CLR.L -(SP) CLR.L -(SP)
MOVE #4,-(SP) PEA 4
MOVE.L #$160000,D0 ;_QDExtensions -> _NewGWorld MOVE.L #$160000,D0 ;_QDExtensions -> _NewGWorld
DC.W $AB1D DC.W $AB1D
MOVE (SP)+, D4 MOVE (SP)+, D4
@@ -1822,7 +1822,7 @@ share LINK A6,#VARSIZE ;ALLOCATE STACK FRAME
MOVEA.L $2(A3), A0 MOVEA.L $2(A3), A0
_HLock _HLock
MOVE.L (A0), MASKBITS(A6) MOVE.L (A0), MASKBITS(A6)
MOVE.L #$160000,D0 ;_QDExtensions -> _NewGWorld MOVE.L #$80005,D0 ;_QDExtensions -> _GetGWorld
DC.W $AB1D DC.W $AB1D
@skip @skip
@@ -2416,7 +2416,7 @@ cutOutDevices
cmp.l ctSeed(a0),d1 ;do the color tables seeds match ? cmp.l ctSeed(a0),d1 ;do the color tables seeds match ?
beq @next beq @next
movem.l d1/a1,-(sp) ;save our scratch registers movem.l d1/a1-a3,-(sp) ;save our scratch registers
clr.b -(sp) ;make space for boolean result clr.b -(sp) ;make space for boolean result
pea tempRect1(a6) ;pointer to the SrcRect in global coordinates pea tempRect1(a6) ;pointer to the SrcRect in global coordinates
@@ -2433,26 +2433,26 @@ cutOutDevices
move.l pmTable(a0),a0 move.l pmTable(a0),a0
move.l (a0),a0 move.l (a0),a0
move.l (DeviceList),a2 move.l (DeviceList),a2
move.l (a2),a2 @again move.l (a2),a2
move.l GDPMap(a2),a3 move.l GDPMap(a2),a3
move.l (a3),a3 move.l (a3),a3
move.l pmTable(a3),a3 move.l pmTable(a3),a3
move.l (a3),a3 move.l (a3),a3
move.l (a3),d0 move.l (a3),d0
@again Cmp.L (a0),d0 cmp.l (a0),d0
bne @done bne @done
sub #$8,sp sub.l #8,sp
clr.b -(sp) clr.b -(sp)
pea.l tempRect1(a6) pea.l tempRect1(a6)
pea.l $22(a2) pea.l $22(a2)
pea.l $a(sp) pea.l $a(sp)
_SectRect _SectRect
tst.b (sp)+ tst.b (sp)+
add #8,sp add.l #8,sp
bne @skip bne @skip
@done Move.L GDNextGD(a2),d0 @done move.l GDNextGD(a2),d0
move.l d0,a2 move.l d0,a2
bne.b @again bne.s @again
lea tempRect2(a6),a0 ;point to our temp rect lea tempRect2(a6),a0 ;point to our temp rect
pea topleft(a0) ;convert the temp rect back to local coordinates pea topleft(a0) ;convert the temp rect back to local coordinates
@@ -2468,7 +2468,7 @@ cutOutDevices
move.l d6,-(sp) move.l d6,-(sp)
_DiffRgn _DiffRgn
@skip movem.l (sp)+,d1/a1 ;restore our scratch registers @skip movem.l (sp)+,d1/a1-a3 ;restore our scratch registers
@next move.l (a1),a0 ;deref the current device list handle @next move.l (a1),a0 ;deref the current device list handle
move.l GDNextGD(a0),d0 ;get the next device handle into D0 move.l GDNextGD(a0),d0 ;get the next device handle into D0

View File

@@ -102,12 +102,32 @@
cursorShadow EQU 0 cursorShadow EQU 0
ShieldCursor PROC EXPORT
;---------------------------------------------------------
;
; PROCEDURE ShieldCursor(shieldRect: Rect; offset: Point);
;
; ALL REGS PRESERVED.
;
; Lifted from LCursor.a
;
IMPORT QDNew_OtherShieldCursor
MOVEM.L D0-D2/A0-A1,-(SP) ;SAVE REGS
MOVE.L 28(SP),D0
MOVE.L 24(SP),D1
MOVE.L D0,-(SP) ;PUSH GLOBAL TOP
MOVE.L D1,-(SP) ;PUSH GLOBAL LEFT
JSR QDNew_OtherShieldCursor
MOVEM.L (SP)+,D0-D2/A0-A1 ;RESTORE REGS
RTD #8
CRSRCORE PROC EXPORT CRSRCORE PROC EXPORT
EXPORT InitCrTable EXPORT InitCrTable
EXPORT PinRect EXPORT PinRect
ds.b 48
IMPORT _HideCursor IMPORT _HideCursor
IMPORT _ShowCursor IMPORT _ShowCursor
IMPORT _ShieldCursor IMPORT _ShieldCursor

View File

@@ -221,8 +221,8 @@ SlotParms EQU IOPBlk-spBlock.SPBlockSize ; parameter block for slot manag
VidParms EQU SlotParms-12 ; [12] size of mode params VidParms EQU SlotParms-12 ; [12] size of mode params
StartList EQU VidParms-4 ; [long] pointer to start of resource StartList EQU VidParms-4 ; [long] pointer to start of resource
VARSIZE EQU StartList ; size of local vars for CheckDevices VARSIZE EQU StartList-4 ; size of local vars for CheckDevices
UTILVARS EQU VidParms ; size of local vars for utility routines UTILVARS EQU VidParms-$30 ; size of local vars for utility routines
; <20><><EFBFBD> Start of Code <20><><EFBFBD> ; <20><><EFBFBD> Start of Code <20><><EFBFBD>
; ;
@@ -318,6 +318,8 @@ SetDevGamma
NewFunc
Link A6,#-$B4 Link A6,#-$B4
Move.l A2,-(SP) Move.l A2,-(SP)
Move.l (A0),A2 Move.l (A0),A2
@@ -344,7 +346,7 @@ CheckDevices ; <19>: Moved label from within if-endif to embed utility
; stuff AFTER the GotScrn entrypoint. ; stuff AFTER the GotScrn entrypoint.
LINK A6,#VARSIZE ; allocate local stack frame LINK A6,#VARSIZE ; allocate local stack frame
MOVEM.L A0-A6/D0-D7,-(SP) ; so we don<6F>t screw up the boot process MOVEM.L A0-A4/D0-D7,-(SP) ; so we don<6F>t screw up the boot process
Move.l DeviceList,A0 ; A0 contains gDevice. Move.l DeviceList,A0 ; A0 contains gDevice.
Move.l #-1,A1 ; Use gDevice<63>s PixMap for colorTable. Move.l #-1,A1 ; Use gDevice<63>s PixMap for colorTable.
@@ -405,10 +407,9 @@ NoGammaFix
Cmp.b #15,D0 Cmp.b #15,D0
Bcs.b @dont Bcs.b @dont
Move.l A3,A0 Move.l A3,A0
Bsr.w CheckDevices Bsr.w NewFunc
nop Bne.s @reallyDont
Bne.s * + $4A Bra.s @skipGD
Bra.s * + $62
@dont @dont
Lea SlotParms(A6),A0 ; Fill out SpBlock: Lea SlotParms(A6),A0 ; Fill out SpBlock:
@@ -433,6 +434,8 @@ NoGammaFix
; We found a non-TFB card that contains no gamma table directory. So, we need to ; We found a non-TFB card that contains no gamma table directory. So, we need to
; employ our fix, which is to make a SetGamma and then a SetEntries call. ; employ our fix, which is to make a SetGamma and then a SetEntries call.
@reallyDont
Move.l A2,A0 ; Lock down the gammaTable Handle. Move.l A2,A0 ; Lock down the gammaTable Handle.
_Hlock _Hlock
@@ -620,7 +623,7 @@ DoDrvrPatches
; ;
; Save all registers to prevent problems with the ROM INIT running code. ; Save all registers to prevent problems with the ROM INIT running code.
; ;
MOVEM.L A0-A6/D0-D7,-(SP) ; so we don<6F>t screw up the boot process MOVEM.L A5-A6,-(SP) ; so we don<6F>t screw up the boot process
; ;
; Point to UnitTable in A2. ; Point to UnitTable in A2.

View File

@@ -637,7 +637,7 @@ Seed
MOVE.L D5,D4 ; copy total # of color (and cleared hi word) MOVE.L D5,D4 ; copy total # of color (and cleared hi word)
SUBQ #2,D4 ; this is the number of colors remaining SUBQ #2,D4 ; this is the number of colors remaining
BLE.S QVille ; if zero or negative, all done BLT.S QVille ; if zero or negative, all done
MOVEQ #1,D5 ; start at color #1 (zero based) MOVEQ #1,D5 ; start at color #1 (zero based)
@TheRestOfUs ; a temporary label for the rest of us @TheRestOfUs ; a temporary label for the rest of us
BSR.S QUtil ; queue it BSR.S QUtil ; queue it

View File

@@ -2921,6 +2921,7 @@ _EmptyHandle OPWORD $A000+43
_InitApplZone OPWORD $A000+44 _InitApplZone OPWORD $A000+44
_SetApplLimit OPWORD $A000+45 _SetApplLimit OPWORD $A000+45
_BlockMove OPWORD $A000+46 _BlockMove OPWORD $A000+46
_BlockMoveData OPWORD $A000+46+$200
; Here are the event manager routines ; Here are the event manager routines

View File

@@ -362,6 +362,8 @@ oldBaseAddr DS.B 4 ; old base address, for later comparison
oldPort DS.B 4 ; thePort, before we got here oldPort DS.B 4 ; thePort, before we got here
oldColor DS.B 8 ; a colorSpec used to reinstantiate fg/bk oldColor DS.B 8 ; a colorSpec used to reinstantiate fg/bk
DS.B 356
VARSIZE DS.B 0 ; size of locals VARSIZE DS.B 0 ; size of locals
ENDR ENDR

View File

@@ -1047,7 +1047,7 @@ createPixMap
; Create a dummy inverse table (doesn't have to be a seed) ; Create a dummy inverse table (doesn't have to be a seed)
moveq #2,d0 ; small handle for dummy inverse table moveq #4,d0 ; small handle for dummy inverse table
_NewHandle ,CLEAR ; allocate it _NewHandle ,CLEAR ; allocate it
bne reportError ; if Memory Manager error, report it and quit bne reportError ; if Memory Manager error, report it and quit
@@ -1171,7 +1171,7 @@ dontCloneCTab
; Allocate inverse table to its initial size ; Allocate inverse table to its initial size
moveq #2,d0 ; initial size is 2 moveq #4,d0 ; initial size is 2
_NewHandle ,CLEAR ; allocate it _NewHandle ,CLEAR ; allocate it
bne reportError ; if Memory Manager error, report it and quit bne reportError ; if Memory Manager error, report it and quit
@@ -1417,7 +1417,7 @@ disposOffscreenHandles
cmp #cPortFlag,d0 ; is it set? cmp #cPortFlag,d0 ; is it set?
bne.s @0 ; if not set, don't close port bne.s @0 ; if not set, don't close port
move.l (a0),-(sp) ; push pointer to port move.l (a0),-(sp) ; push pointer to port
_ClosePort ; close it down _CloseCPort ; close it down
@0 @0
move.l d7,a0 ; get handle to offscreen port move.l d7,a0 ; get handle to offscreen port
_DisposHandle ; dispose it _DisposHandle ; dispose it
@@ -1754,7 +1754,7 @@ dontDisposeBaseAddr
dontDisposeGDevice dontDisposeGDevice
move.l offscreenGWorld(sp),-(sp) ; push pointer to offscreen port move.l offscreenGWorld(sp),-(sp) ; push pointer to offscreen port
_ClosePort ; get rid of all substructures _CloseCPort ; get rid of all substructures
move.l offscreenGWorld(sp),a0 ; get pointer to grafport move.l offscreenGWorld(sp),a0 ; get pointer to grafport
_RecoverHandle ; find handle to grafport _RecoverHandle ; find handle to grafport

View File

@@ -40,11 +40,7 @@ AllocCursor PROC EXPORT
; PROCEDURE AllocCursor; ; PROCEDURE AllocCursor;
; ;
LEA AllocCrsr,A0 ;get default cursor routine JMP AllocCrsr
MOVE.L JAllocCrsr,D0 ;has vector been initialized?
BEQ.S @0 ;=>no, use default routine
MOVE.L D0,A0 ;else use routine in vector
@0 JMP (A0) ;and call it
InitCursor PROC EXPORT InitCursor PROC EXPORT
@@ -55,8 +51,8 @@ InitCursor PROC EXPORT
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QUICKDRAW GLOBALS MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QUICKDRAW GLOBALS
PEA ARROW(A0) ;PUSH ADDR OF ARROW PEA ARROW(A0) ;PUSH ADDR OF ARROW
_SetCursor ;INSTALL ARROW CURSOR _SetCursor ;INSTALL ARROW CURSOR
MOVE.L JInitCrsr,A0 ;get lo mem pointer IMPORT _InitCursor
JMP (A0) ;and call it JMP _InitCursor
@@ -70,8 +66,8 @@ SetCursor PROC EXPORT
MOVE #16,-(SP) ;HEIGHT:=16 MOVE #16,-(SP) ;HEIGHT:=16
PEA DATA(A0) ;PUSH ADDR OF DATA PEA DATA(A0) ;PUSH ADDR OF DATA
PEA MASK(A0) ;PUSH ADDR OF MASK PEA MASK(A0) ;PUSH ADDR OF MASK
MOVE.L JSetCrsr,A0 ;get lo mem vector IMPORT _SetCursor
JSR (A0) ;call vector JSR _SetCursor
MOVE.L (SP)+,(SP) ;strip param MOVE.L (SP)+,(SP) ;strip param
RTS ;and return RTS ;and return
@@ -92,8 +88,8 @@ SetCCursor PROC EXPORT
; _SetCursor ; and set it the old way ; _SetCursor ; and set it the old way
MOVE.L 4(SP),-(SP) ; Push handle to color cursor MOVE.L 4(SP),-(SP) ; Push handle to color cursor
MOVE.L JSetCCrsr,A0 ; get lo mem vector IMPORT _SetCCursor
JSR (A0) ; call vector (but don't call him hector) JSR _SetCCursor
; _ShowCursor ; balance is a virtue ; _ShowCursor ; balance is a virtue
MOVE.L (SP)+,(SP) ; strip param MOVE.L (SP)+,(SP) ; strip param
RTS ; and return RTS ; and return
@@ -107,8 +103,8 @@ HideCursor PROC EXPORT
; ;
; ALL REGS PRESERVED. ; ALL REGS PRESERVED.
; ;
MOVE.L JHideCursor,-(SP) ;get lo mem vector IMPORT _HideCursor
RTS ;and call it JMP _HideCursor
@@ -119,36 +115,8 @@ ShowCursor PROC EXPORT
; ;
; ALL REGS PRESERVED. ; ALL REGS PRESERVED.
; ;
MOVE.L JShowCursor,-(SP) ;get lo mem vector IMPORT _ShowCursor
RTS ;and call it JMP _ShowCursor
ShieldCursor PROC EXPORT
;---------------------------------------------------------
;
; PROCEDURE ShieldCursor(shieldRect: Rect; offset: Point);
;
; ALL REGS PRESERVED.
;
MOVEM.L D0-D3/A0-A1,-(SP) ;SAVE REGS
MOVE.L 32(SP),A0 ;POINT TO SHIELDRECT
MOVEM.W (A0)+,D0/D1/D2/D3 ;GET TOP ... RIGHT
LEA 28(SP),A1
SUB (A1),D0 ;TOP - OFFSET.V
SUB (A1)+,D2 ;BOTTOM - OFFSET.V
SUB (A1),D1 ;LEFT - OFFSET.H
SUB (A1),D3 ;RIGHT - OFFSET.H
MOVE D1,-(SP) ;PUSH GLOBAL LEFT
MOVE D0,-(SP) ;PUSH GLOBAL TOP
MOVE D3,-(SP) ;PUSH GLOBAL RIGHT
MOVE D2,-(SP) ;PUSH GLOBAL BOTTOM
MOVE.L JShieldCursor,A0 ;get lo mem vector
JSR (A0) ;and call it
MOVEM.L (SP)+,D0-D3/A0-A1 ;RESTORE REGS
MOVE.L (SP)+,(SP)
MOVE.L (SP)+,(SP) ;STRIP 8 BYTES
RTS ;AND RETURN
@@ -159,13 +127,8 @@ ObscureCursor PROC EXPORT
; ;
; Hide the cursor image until the next time the mouse moves. ; Hide the cursor image until the next time the mouse moves.
; ;
MOVE.L JCrsrObscure,A0 ;get lo mem vector IMPORT _ObscureCursor
JMP (A0) ;and call it JMP _ObscureCursor
ds.b 32
ENDPROC ENDPROC

View File

@@ -694,7 +694,7 @@ linkSize DS.B 0 ; linky number
PEA inFront(A6) PEA inFront(A6)
_SameProcess ; are we the front process? _SameProcess ; are we the front process?
ADDQ #2,SP ; OSErr leaves inFront true from above ADDQ #2,SP ; OSErr leaves inFront true from above
TST inFront(A6) TST.B inFront(A6)
BEQ.S @doNothing BEQ.S @doNothing
@front @front
@@ -1841,7 +1841,7 @@ linkSize DS.B 0 ;linky number
BNE.S GoHome ; No=> go home w/false BNE.S GoHome ; No=> go home w/false
MOVE $14(A3),D0 MOVE $14(A3),D0
AND #$8010,D0 AND #$8010,D0
BPL.S GoHome ; No=> ditto BEQ.S GoHome ; No=> ditto
SUBQ #4,SP ; space for result <dvb5> SUBQ #4,SP ; space for result <dvb5>
MOVE.L A2,-(SP) ; push gDevice handle <dvb5> MOVE.L A2,-(SP) ; push gDevice handle <dvb5>
JSR GetClut ; get the appropriate default clut <dvb5> JSR GetClut ; get the appropriate default clut <dvb5>
@@ -3188,9 +3188,9 @@ SetDev
Move.L (A0),A0 ; dereference it Move.L (A0),A0 ; dereference it
TST gdType(A0) ; is it CLUT type (zero)? dvb1 TST gdType(A0) ; is it CLUT type (zero)? dvb1
BNE GoHome ; No => do nothing BNE GoHome ; No => do nothing
MOVE $14(A3),D0 MOVE $14(A0),D0
AND #$8010,D0 AND #$8010,D0
BPL GoHome ; No=>go home BEQ GoHome ; No=>go home
Move.L gdPMap(A0),A0 ; get handle to pixmap Move.L gdPMap(A0),A0 ; get handle to pixmap
Move.L (A0),A0 ; dereference pixmap Move.L (A0),A0 ; dereference pixmap
Move.L pmTable(A0),A0 ; get handle to CTab Move.L pmTable(A0),A0 ; get handle to CTab

View File

@@ -2350,11 +2350,11 @@ NEXTGD move.l (a2),a0
lea dstRectRgn+rgnBBox(A6),a0 lea dstRectRgn+rgnBBox(A6),a0
move.l a0,d0 move.l a0,d0
move.l a0,-(sp) move.l a0,-(sp)
jsr ([$FC0]) ; _GlobalToLocal? jsr ([$FC4]) ; _GlobalToLocal?
add #4,d0 add #4,d0
move.l d0,-(sp) move.l d0,-(sp)
jsr ([$FC0]) ; _GlobalToLocal? jsr ([$FC4]) ; _GlobalToLocal?
MOVE.L (A2),A0 ; POINT TO DEVICE MOVE.L (A2),A0 ; POINT TO DEVICE
MOVE.L GDPMAP(A0),A0 ; GET PIXMAP MOVE.L GDPMAP(A0),A0 ; GET PIXMAP

View File

@@ -4245,7 +4245,7 @@ MORE1
MOVE.L A3,A0 ;PTR TO FIRST byte of src MOVE.L A3,A0 ;PTR TO FIRST byte of src
move.l d5,d0 ;get rowbytes in d0 move.l d5,d0 ;get rowbytes in d0
_BlockMove ;copy from there to here _BlockMoveData ;copy from there to here
;assumes here is a 24 bit address ;assumes here is a 24 bit address
moveq #false32b,d0 ;switch back before calling PutPicProc <BAL 02Feb90> moveq #false32b,d0 ;switch back before calling PutPicProc <BAL 02Feb90>

View File

@@ -1389,7 +1389,7 @@ GETPIXEL
MOVEQ #0,D2 ;ROUTINE = GETPIXEL MOVEQ #0,D2 ;ROUTINE = GETPIXEL
SHARE LINK A6,#VARSIZE ;ALLOCATE STACKFRAME SHARE LINK A6,#VARSIZE ;ALLOCATE STACKFRAME
MOVEM.L D4-D5/A2-A3,-(SP) ;SAVE WORK REGISTERS MOVEM.L D4-D6/A2-A3,-(SP) ;SAVE WORK REGISTERS
MOVE.L THEGDEVICE,-(SP) ;SAVE CURRENT GRAFDEVICE MOVE.L THEGDEVICE,-(SP) ;SAVE CURRENT GRAFDEVICE
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QUICKDRAW GLOBALS MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QUICKDRAW GLOBALS
MOVE.L THEPORT(A0),A0 ;GET THEPORT MOVE.L THEPORT(A0),A0 ;GET THEPORT
@@ -4731,7 +4731,7 @@ DSTH EQU SRCH-4
MOVE.L (A0),A0 ; get SRC pointer MOVE.L (A0),A0 ; get SRC pointer
MOVE.L (A1),A1 ; get DST pointer MOVE.L (A1),A1 ; get DST pointer
MOVE.L D1,D0 ; D0 = size MOVE.L D1,D0 ; D0 = size
_BlockMove ; copy the data _BlockMoveData ; copy the data
DONE MOVE.L (SP)+,A0 ; get return address DONE MOVE.L (SP)+,A0 ; get return address
ADDQ #8,SP ; strip parameters ADDQ #8,SP ; strip parameters

View File

@@ -127,7 +127,7 @@ multColor EQU RGNC-2 ;byte, set if source contains nonblack/white colors
; ;
_StackAvail ;GET STACK AVAIL IN D0.L _StackAvail ;GET STACK AVAIL IN D0.L
LSR.L #2,D0 ;CONVERT BYTES TO LONGS LSR.L #2,D0 ;CONVERT BYTES TO LONGS
SUB.L #qdStackXtra,D0 ;SUBTRACT SLOP FACTOR <1.2> BAL SUB.L #$200,D0 ;SUBTRACT SLOP FACTOR <1.2> BAL
MOVE.L D0,STACKFREE(A6) ;AND SAVE FREE LONGS ON STACK MOVE.L D0,STACKFREE(A6) ;AND SAVE FREE LONGS ON STACK
bpl.s @stkOK bpl.s @stkOK
_stNoStack ;=>NOT ENOUGH STACK, QUIT _stNoStack ;=>NOT ENOUGH STACK, QUIT