sys7.1-doc-wip/QuickDraw/QDUtil.a

4529 lines
139 KiB
Plaintext
Raw Permalink Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

;
; Hacks to match MacOS (most recent first):
;
; <Sys7.1> 8/3/92 Elliot make this change
; 9/2/94 SuperMario ROM source dump (header preserved below)
;
;
; File: QDUtil.a
;
; Copyright: © 1981-1990, 1992-1993 by Apple Computer, Inc., all rights reserved.
;
; This file is used in these builds: Mac32 BigBang
;
;
; Change History (most recent first):
;
; <SM7> 9/12/93 joe seperately conditionalize out ElsieTranslate24To32.
; <SM6> 9/12/93 SAM Changed all instances of _Translate24to32 to _rTranslate24to32
; so they can conditionalized out of the build.
; <SM3> 7/16/92 CSS Update from Reality:
; <R21> 6/8/92 SAH #1031825: Changed ColorMap to ignore the multColor flag.
; <SM2> 6/11/92 stb <sm 6/9/92>stb Synch with QDciPatch.a; added comments to
; ColorMap, AlphaDispatch, GetPixel, GetCPixel, FillClipScanLine,
; FillClipOrLine, FAST11, FillClipXLine.
; <20> 11/26/90 SMC Fixed slab pattern hiliting. With BAL.
; <19> 11/6/90 SMC Fixed NOPfgColorTable range problem in Mac32 build. With KON.
; <18> 11/5/90 SMC Fixed FastTab range problem in Mac32 build. With KON.
; <17> 10/31/90 SMC Fixed alpha channel bugs with BAL.
; <16> 10/17/90 SMC Fixed pattern alignment problem in FillClipXLine. With KON.
; <15> 10/17/90 SMC Changed speedup method used in <13> to work in cases where
; someone has put a semi-legal value in fgcolor or bkcolor, such
; as -1 instead of 1. With BAL.
; <14> 10/17/90 KON The default colors in ColorMap should be inverted if Multcolor
; is set and destination is direct. With SMC.
; <13> 10/1/90 KON Speedup to 1-bit fg/bg pixel replication. With BAL.
; <12> 9/27/90 SMC Fixed pattern hilite setup in SlabMode for 16 and 32-bit.
; Slabbed pattern hilite still has problems but now it has one
; less.
; <11> 9/18/90 SMC Fixed GetCPixel to return valid color at points along top and
; left edges of gdevice.
; <10> 9/18/90 BG Removed <6>, <8>. 040s are behaving more reliably now.
; <9> 8/16/90 dba fix up the implementation of VisRgnChanged
; <8> 7/20/90 BG Added some more EclipseNOPs for flakey 040s.
; <7> 7/20/90 gbm Change comment to reflect new reality
; <6> 6/27/90 BG Added NOPs for flakey 040s.
; <5> 6/21/90 KON Fix getPixel and getCPixel so they work with pixmap with
; pmVersion=4 (needs 32-bit addressing).
; <4> 6/4/90 KON Hack to make 1-bit old port copy mode work.
; <3> 3/26/90 KON Add VisRgnChanged call (trap $A0A5).
; <2> 2/28/90 JJ Added the routine ElsieTranslate24To32, a new address
; translation routine appropriate for the VISA decoder.
; <1.8> 11/18/89 BAL Added in QuickerDraw loops for copy mode and 8-bit arithmetic
; DrawSlab
; <•1.7> 7/14/89 BAL For Aurora: Final CQD
; <1.6> 6/30/89 BAL Init FG = black and BK = white flags in ColorMap∂
; <1.5> 6/10/89 CEL Moved Private.a QuickDraw Equates into proper QuickDraw private
; file (colorequ.a), got rid of QuickDraw nFiles dependencies and
; fixed up necessary files…
; <•1.4> 5/29/89 BAL Blasting in 32-Bit QuickDraw version 1.0 Final
; 1/22/89 BAL Altered DrawSlab loops to use patVPos as a long.
; 9/19/88 BAL Altered ColorMap, DrawSlab to use common stack frame file
; 'Drawing Vars.a'
; 9/15/88 BAL Compute slab bit-width as a long
; 5/6/88 BAL Rolled in fix to set bcolor to white during transparent blit
; 5/6/88 BAL Altered ColorMap to clean invColor and colorTable ptrs
; 5/4/88 BAL Modified XorSlab to maintain bit width as a long
; 4/14/88 BAL Modified GetCPixel to operate in 32 bit addressing mode
; 1/21/87 EHB Modified colorMap to check grafPort type before using colors
; 1/3/87 CRC color correction in colorMap; bug fixes in arithmetic modes
; 12/30/86 EHB Modified colorMap to check grafPort type before using colors
; 12/12/86 CRC Added arithmetic modes
; 7/29/86 EHB Use new stack-based EXPAT buffer
; 7/26/86 EHB Added support for expanded patterns
; 7/22/86 EHB In PatExpand, only colorize pattern if copy mode Added color to
; pattern OR and pattern BIC transfer modes in DrawSlab
; 7/7/86 EHB In ColorMap, use portBits+rowBytes (not rowBytes) (oops!)
; 7/2/86 EHB In ColorMap, use bit 13 of rowbytes to draw old-style colors
; into new-style ports.
; 6/22/86 EHB Added multi-depth patexpand (version 0.1)
; 6/20/86 EHB Added compatibility color mapping to COLORMAP
; 6/17/86 EHB Tweaked GetPixel to work with cGrafPorts
; 6/10/86 EHB Redid DrawSlab to use longwords and 020 instructions.
; 6/9/86 EHB Removed long mask routines in lieu of macros (found a better
; way)
; 6/8/86 EHB Redid XORSlab using 020 instructions
; 6/6/86 EHB Added routines LLeftMask,LRightMask,LBitMask
; 4/16/86 EHB Added 0 byte at end of file for alignment
;
BLANKS ON
STRING ASIS
MACHINE MC68020
;-------------------------------------------------------------
;
; --> UTIL.TEXT
;
; SMALL UTILITY ROUTINES USED BY QuickDraw
;
; MODIFICATIONS
; 16Apr86 EHB Added 0 byte at end of file for alignment
; 6Jun86 EHB Added routines LLeftMask,LRightMask,LBitMask
; 8Jun86 EHB Redid XORSlab using 020 instructions
; 9Jun86 EHB Removed long mask routines in lieu of macros (found a better way)
; 10Jun86 EHB Redid DrawSlab to use longwords and 020 instructions.
; 17Jun86 EHB Tweaked GetPixel to work with cGrafPorts
; 20Jun86 EHB Added compatibility color mapping to COLORMAP
; 22Jun86 EHB Added multi-depth patexpand (version 0.1)
; 2Jul86 EHB In ColorMap, use bit 13 of rowbytes to draw old-style colors
; into new-style ports.
; 7Jul86 EHB In ColorMap, use portBits+rowBytes (not rowBytes) (oops!)
; 22Jul86 EHB In PatExpand, only colorize pattern if copy mode
; Added color to pattern OR and pattern BIC transfer modes in DrawSlab
; 26Jul86 EHB Added support for expanded patterns
; 29Jul86 EHB Use new stack-based EXPAT buffer
; 12Dec86 CRC Added arithmetic modes
; 30Dec86 EHB Modified colorMap to check grafPort type before using colors
; 3Jan87 CRC color correction in colorMap; bug fixes in arithmetic modes
; 21Jan87 EHB Modified colorMap to check grafPort type before using colors
; 14Apr88 BAL Modified GetCPixel to operate in 32 bit addressing mode
; 04May88 BAL Modified XorSlab to maintain bit width as a long
; 06May88 BAL Altered ColorMap to clean invColor and colorTable ptrs
; 06May88 BAL Rolled in fix to set bcolor to white during transparent blit
; 15Sep88 BAL Compute slab bit-width as a long
; 19Sep88 BAL Altered ColorMap, DrawSlab to use common stack frame file 'Drawing Vars.a'
; 22Jan89 BAL Altered DrawSlab loops to use patVPos as a long.
VisRgnChanged PROC EXPORT ;<26MAR90 KON>
;-----------------------------------------------------------
;
; Procedure VisRgnChanged(thePort: GrafPort);
;
; This call will be needed for video windows so the mask plane
; for touchstone can be updated. Non-video QD simply returns.
;
rts
ENDPROC
BitNot FUNC EXPORT
;-----------------------------------------------------------
;
; Function BitNot(long: LongInt): LongInt;
;
MOVE.L (SP)+,A0 ;POP RETURN ADDR
NOT.L (SP) ;INVERT LONG
MOVE.L (SP)+,(SP) ;STORE INTO RESULT
JMP (A0) ;AND RETURN
BitAnd FUNC EXPORT
EXPORT BitXor,BitOr,BitShift
;-----------------------------------------------------------
;
; Function BitAnd(long1,long2: LongInt): LongInt;
;
MOVE.L (SP)+,A0 ;POP RETURN ADDR
MOVE.L (SP)+,D0 ;GET ONE LONG
AND.L (SP)+,D0 ;AND IT WITH THE OTHER
BRA.S DONE ;AND STORE RESULT
;-----------------------------------------------------------
;
; Function BitXor(long1,long2: LongInt): LongInt;
;
BitXor MOVE.L (SP)+,A0 ;POP RETURN ADDR
MOVE.L (SP)+,D0 ;GET ONE LONG
MOVE.L (SP)+,D1 ;GET THE SECOND
EOR.L D1,D0 ;XOR BOTH
BRA.S DONE ;AND STORE RESULT
;-----------------------------------------------------------
;
; Function BitOr(long1,long2: LongInt): LongInt;
;
BitOr MOVE.L (SP)+,A0 ;POP RETURN ADDR
MOVE.L (SP)+,D0 ;GET ONE LONG
OR.L (SP)+,D0 ;OR IT WITH THE OTHER
BRA.S DONE ;AND STORE RESULT
;-----------------------------------------------------------
;
; Function BitShift(long: LongInt; count: INTEGER): LongInt;
;
; positive count --> shift left.
; negative count --> shift right.
;
BitShift MOVE.L (SP)+,A0 ;POP RETURN ADDR
MOVE (SP)+,D1 ;GET COUNT
BPL.S SHLEFT ;SHIFT LEFT IF POSITIVE
NEG D1 ;MAKE COUNT POSITIVE
MOVE.L (SP)+,D0 ;GET LONG
LSR.L D1,D0 ;SHIFT IT RIGHT
BRA.S DONE ;AND STORE RESULT
SHLEFT MOVE.L (SP)+,D0 ;GET LONG
LSL.L D1,D0 ;SHIFT IT LEFT
DONE MOVE.L D0,(SP) ;STORE THE RESULT
JMP (A0) ;AND RETURN
BitTst FUNC EXPORT
EXPORT BitSet,BitClr
;---------------------------------------------------------
;
; FUNCTION BitTst(bytePtr: Ptr; bitNum: LongInt): BOOLEAN;
;
BSR.S SHARE
MOVE.L (SP)+,A1 ;GET PTR
BTST D0,0(A1,D1.L) ;TEST THE BIT
SNE (SP) ;SET OR CLEAR RESULT
NEG.B (SP) ;CONVERT -1 TO 1
JMP (A0) ;RETURN
;---------------------------------------------------------
;
; PROCEDURE BitSet(bytePtr: Ptr; bitNum: LongInt);
;
BitSet BSR.S SHARE
MOVE.L (SP)+,A1 ;GET PTR
BSET D0,0(A1,D1.L) ;SET THE BIT
; needed for flakey 040s <6>
JMP (A0)
;---------------------------------------------------------
;
; PROCEDURE BitClr(bytePtr: Ptr; bitNum: LongInt);
;
BitClr BSR.S SHARE
MOVE.L (SP)+,A1 ;GET PTR
BCLR D0,0(A1,D1.L) ;SET THE BIT
JMP (A0)
;
;
;
SHARE MOVE.L (A7)+,A1
MOVE.L (SP)+,A0 ;POP RETURN ADDR
MOVE.L (SP)+,D1 ;GET BITNUM
MOVE D1,D0 ;COPY IT
ASR.L #3,D1 ;CONVERT BITS TO BYTES
NOT D0 ;REVERSE BIT SENSE
JMP (A1)
Random FUNC EXPORT
;--------------------------------------------------------------
;
; FUNCTION Random: INTEGER;
;
; returns a signed 16 bit number, and updates unsigned 32 bit randSeed.
;
; recursion is randSeed := (randSeed * 16807) MOD 2147483647.
;
; See paper by Linus Schrage, A More Portable Fortran Random Number Generator
; ACM Trans Math Software Vol 5, No. 2, June 1979, Pages 132-138.
;
; Clobbers D0-D2, A0
;
;
; GET LO 16 BITS OF SEED AND FORM LO PRODUCT
; xalo := A * LoWord(seed)
;
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QuickDraw GLOBALS
MOVE #16807,D0 ;GET A = 7^5
MOVE D0,D2 ;GET A = 7^5
MULU RANDSEED+2(A0),D0 ;CALC LO PRODUCT = XALO
;
; FORM 31 HIGHEST BITS OF LO PRODUCT
; fhi:=HiWord(seed) * ORD4(a) + HiWord(xalo);
;
MOVE.L D0,D1 ;COPY xalo
CLR.W D1
SWAP D1 ;GET HiWord(xalo) as a long
MULU RANDSEED(A0),D2 ;MULT BY HiWord(seed)
ADD.L D1,D2 ;ADD LEFTLO = FHI
;
; GET OVERFLOW PAST 31ST BIT OF FULL PRODUCT
; k:=fhi DIV 32768;
;
MOVE.L D2,D1 ;COPY FHI
ADD.L D1,D1 ;CALC 2 TIMES FHI
CLR.W D1
SWAP D1 ;CALC FHI SHIFTED RIGHT 15 FOR K
;
; ASSEMBLE ALL THE PARTS AND PRE-SUBTRACT P
; seed:=((BitAnd(XALO,$0000FFFF) - P) + BitAnd(fhi,$00007FFF) * b16) + K;
;
AND.L #$0000FFFF,D0 ;GET LO WORD XALO
SUB.L #$7FFFFFFF,D0 ;SUBTRACT P = 2^31-1
AND.L #$00007FFF,D2 ;BitAnd(fhi,$00007FFF)
SWAP D2 ;TIMES 64K
ADD.L D1,D2 ;PLUS K
ADD.L D2,D0 ;CALC TOTAL
;
; IF seed < 0 THEN seed:=seed+p;
;
BPL.S UPDATE
ADD.L #$7FFFFFFF,D0
UPDATE MOVE.L D0,RANDSEED(A0) ;UPDATE SEED
CMP.W #$8000,D0 ;IS NUMBER -32768 ?
BNE.S NUMOK ;NO, CONTINUE
CLR D0 ;YES, RETURN ZERO INSTEAD
NUMOK MOVE.W D0,4(SP) ;RETURN LO WORD AS RESULT
RTS
ForeColor PROC EXPORT
EXPORT BackColor,PortLong,ColorBit,PortWord
;--------------------------------------------------------------
;
; PROCEDURE ForeColor(color: LongInt);
;
MOVEQ #FGCOLOR,D0 ;GET OFFSET TO FGCOLOR
CSHARE MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QuickDraw GLOBALS
MOVE.L THEPORT(A0),A0 ;POINT TO THEPORT
TST PORTBITS+ROWBYTES(A0) ;OLD OR NEW PORT?
BPL.S PORTLONG ;=>OLD PORT, INSTALL LONG INTO PORT
MOVE D0,-(SP) ;SAVE OFFSET TO COLOR FIELD
MOVE.L 6(SP),D0 ;GET COLOR (xxxC MYBr gbwb)
MOVE.L PORTBITS+BASEADDR(A0),A0 ;GET HANDLE TO PORT PIXMAP
MOVE.L (A0),A0 ;POINT TO PIXMAP
; CONVERT THE PLANAR BITS (xxxC MYBr gbwb) TO AN RGB VALUE
LSR.L #1,D0 ;CHECK FOR WHITE (->CMYB rgbw)
BCS.S @0 ;=>NOT WHITE
OR #$00E0,D0 ;ELSE SET WHITE BITS (CMY = 111)
@0 LSR #5,D0 ;SHIFT CMY INTO LOW NIBBLE
AND #$7,D0 ;CLEAR ALL BUT LOW NIBBLE
MOVE.L QDCOLORS,A0 ;POINT TO DEFAULT COLORS
; SET THE SPECIFIED COLOR
PEA 2(A0,D0*8) ;PUSH ADDRESS OF RGB
CMP #FGCOLOR,4(SP) ;ARE WE SETTING THE FORECOLOR?
BNE.S DOBACK ;=> NO, SET BACKCOLOR
_RGBFORECOLOR ;SET THE FOREGROUND COLOR
BRA.S DONE ;=>AND RETURN
DOBACK _RGBBACKCOLOR ;ELSE SET THE BACKGROUND COLOR
DONE MOVE (SP)+,D0 ;POP THE OFFSET
MOVE.L (SP)+,A1 ;GET THE RETURN ADDRESS
ADDQ #4,SP ;STRIP THE PARAMETER
JMP (A1) ;AND RETURN
;--------------------------------------------------------------
;
; PROCEDURE BackColor(color: LongInt);
;
BackColor
MOVEQ #BKCOLOR,D0 ;GET OFFSET TO BKCOLOR
BRA.S CSHARE ;INSTALL COLOR INTO PORT
;-------------------------------------------------------
;
; PROCEDURE PortLong(long: LongInt);
; INSTALL A LONG INTO CURRENT GRAFPORT. ENTER WITH OFFSET IN D0
;
PortLong
MOVE.L (SP)+,A1 ;POP RETURN ADDR
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QuickDraw GLOBALS
MOVE.L THEPORT(A0),A0 ;POINT TO THEPORT
MOVE.L (SP)+,0(A0,D0) ;INSTALL LONG INTO THEPORT
JMP (A1) ;AND RETURN
;--------------------------------------------------------------
;
; PROCEDURE ColorBit(whichBit: INTEGER);
;
ColorBit
MOVEQ #COLRBIT,D0 ;GET OFFSET TO COLRBIT
;FALL THRU INTO PORTWORD
;-------------------------------------------------------
;
; PROCEDURE PortWord(word: INTEGER);
; INSTALL A WORD INTO CURRENT GRAFPORT. ENTER WITH OFFSET IN D0
;
PortWord
MOVE.L (SP)+,A1 ;POP RETURN ADDR
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QuickDraw GLOBALS
MOVE.L THEPORT(A0),A0 ;POINT TO THEPORT
MOVE.W (SP)+,0(A0,D0) ;INSTALL WORD INTO THEPORT
JMP (A1) ;AND RETURN
GetMaskTab PROC EXPORT
EXPORT LeftMask,RightMask,BitMask,MaskTab
;----------------------------------------------------------
;
; ASSEMBLY LANGUAGE CALLABLE PROCEDURES LEFTMASK, RIGHTMASK, AND BITMASK:
;
; ENTER WITH COORDINATE IN D0, RETURNS WITH 16 BIT MASK IN D0
; NO OTHER REGISTERS ALTERED.
;
LEA MaskTab,A0 ;POINT TO MASK TABLE
RTS ;AND RETURN
LeftMask
AND #$F,D0 ;TREAT MOD 16
ADD D0,D0 ;DOUBLE FOR TABLE
MOVE MASKTAB+32(D0),D0 ;GET LEFTMASK
RTS
RIGHTMASK
AND #$F,D0 ;TREAT MOD 16
ADD D0,D0 ;DOUBLE FOR TABLE
MOVE MASKTAB(D0),D0 ;GET RIGHT MASK
RTS
BITMASK AND #$F,D0 ;TREAT MOD 16
ADD D0,D0 ;DOUBLE FOR TABLE
MOVE MASKTAB+64(D0),D0 ;GET BITMASK
RTS
MASKTAB DC.W $0000,$8000,$C000,$E000 ;TABLE OF 16 RIGHT MASKS
DC.W $F000,$F800,$FC00,$FE00
DC.W $FF00,$FF80,$FFC0,$FFE0
DC.W $FFF0,$FFF8,$FFFC,$FFFE
DC.W $FFFF,$7FFF,$3FFF,$1FFF ;TABLE OF 16 LEFT MASKS
DC.W $0FFF,$07FF,$03FF,$01FF
DC.W $00FF,$007F,$003F,$001F
DC.W $000F,$0007,$0003,$0001
DC.W $8000,$4000,$2000,$1000 ;TABLE OF 16 BIT MASKS
DC.W $0800,$0400,$0200,$0100
DC.W $0080,$0040,$0020,$0010
DC.W $0008,$0004,$0002,$0001
; translation for arithmetic modes when drawn at 1 bit per pixel
arithMode PROC EXPORT
; hilite
;avg addPin addOver subPin trans max subOver min
DC.B srcCopy, srcBic, srcXor, srcOr, srcOr, srcBic, srcXor, srcOr
ColorMap PROC EXPORT
IMPORT arithMode
IMPORT NOPfgColorTable
; rolled in from QDciPatchROM.a <sm 6/9/92>stb
;----------------------------------------------------------------
;
; PROCEDURE ColorMap: (pat: Pattern; mode: INTEGER);
;
; ADJUST INPUT MODE AND PATTERN TO ACCOMPLISH COLOR SEPARATION.
; POTENTIALLY MODIFIES: LOCMODE, NEWPATTERN, LOCPAT, FCOLOR, BCOLOR.
;
; ADJUSTED MODE IS RETURNED IN LOCMODE(A6).
; IF PATTERN IS ADJUSTED, THEN NEWPATTERN(A6) IS SET FALSE AND LOCPAT(A6) IS MODIFIED.
; FCOLOR(A6) AND BCOLOR(A6) ARE MODIFIED AS DESCRIBED BELOW.
;
; IF OLD PORT, TRANSLATES OLD-STYLE FGCOLOR, BKCOLOR INTO AN RGB,
; AND THEN GETS THE INDEX FOR THAT COLOR. FOR ALL PORTS, THE
; RETURNED COLOR CONTAINS THE PIXEL REPLICATED THROUGHOUT THE LONG
; (SUITABLE FOR MASKING).
;
; FOR EITHER MODE, IF THE DESTINATION IS ONE BIT DEEP, DO PLANAR REMAPPING
; SO THAT FASTEST COPYBITS BLT ROUTINES DON'T NEED TO APPLY COLOR.
;
; CLOBBERS A0-A1,D0-D2
;
; CALLED BY: DRAWARC, DRAWLINE, STRETCH
; A6 STACK FRAME ALLOCATED BY CALLER, USED LOCALLY.
;-------------------------------------------------
;
; A6 OFFSETS OF LOCAL VARIABLES AFTER LINK:
;
;
&CurFile SETC 'COLORMAP'
INCLUDE 'DrawingVars.a'
;-------------------------------------------------
PARAMSIZE EQU 0 ;SIZE OF PARAMETERS
VARSIZE EQU 0 ;SIZE OF LOCALS
; LINK A4,#VARSIZE ;MAKE A STACK FRAME
MOVEM.L D3-D7/A2-A3,-(SP) ;SAVE REGS
MOVE.L GRAFGLOBALS(A5),A2 ;POINT TO QUICKDRAW GLOBALS
MOVE.L THEPORT(A2),A2 ;POINT TO THE PORT
MOVE locMode(A6),D3 ;get the mode
MOVE.L FGCOLOR(A2),D6 ;GET FOREGROUND COLOR INTO D6
MOVE.L BKCOLOR(A2),D7 ;GET BACKGROUND COLOR INTO D7
; <1.6> BAL
@modeOK MOVE D3,D1 ;make a copy of the mode
AND #$FFF7,D3 ;clear the pattern bit
EOR D3,D1 ;set only the pattern bit
CMP #srcXor,D3 ;could it be replaced by hilite?
BNE.S @noXorSub
BSET #hiliteBit,HiliteMode ;check to see if highlight bit was set
BNE.S @noXorSub ;if not, invert old way
MOVE #$32,D3 ;set to src highlight
@noXorSub
BTST #5,D3 ;an arithmetic mode?
BEQ.S @leaveModeAlone ;skip if no mode
CMP #1,dstPix+pixelSize(A6) ;1 bit per pixel on the destination
BNE.S @leaveModeAlone
AND #$07,D3 ;get variants
MOVE.B arithMode(D3),D3 ;get mapped mode in 1 bit
@leaveModeAlone
OR D1,D3 ;combine mapped mode and pattern bit
MOVE D3,locMode(A6) ;save off altered mode
; <17> Beginning of alpha channel changes
CLR.B alphaMode(A6) ;clear the alpha mode to default
BTST #5,D3 ;check again for arithmetic modes
BNE @noalpha ;skip alpha stuff if arithmetic
MOVE.W dstShift(A6),D0 ;yes, get pixel size
; MOVE.L ((NOPfgColorTable-*).L,PC,D0.W*4),D0
LEA (NOPfgColorTable-*).L,A1 ;get distance from here to NOPfgColorTable
LEA *-6(A1.L),A1 ;get address of "white" table
MOVE.L 0(A1,D0.W*4),D0 ;get default mask for current depth
MOVE.L D0,alphaBack(A6) ;save for later use
MOVE.W D3,D5 ;make copy of adjusted mode
AND.W #$03,D5 ;mask off all but base mode
CMP.W #srcXor,D5 ;are we xoring?
BEQ.S @1 ;yes, use normal default mask
MOVEQ #-1,D0 ;get all ones
@1: MOVE.L D0,alphaMask(A6) ;save default alphaMask
TST portBits+rowBytes(A2) ;is it an old port?
BPL @noalpha ;yes, alpha mode is illegal
MOVE.W dstPix+pixelSize(A6),D0 ;get depth of destination
CMP.W #16,D0 ;direct device?
BLT.S @noalpha ;no, skip this stuff ; <SM4>
MOVE.L grafVars(A2),D4 ;get grafvars handle
BEQ @noalpha ;no grafvars, no alpha
MOVE.L D4,A0 ;copy handle
MOVE.L (A0),A1 ;dereference handle
BTST #PmNewGVBit-8,pmFlags(A1) ;make sure grafvars have been expanded
BEQ.S @noalpha ;if not, bail
MOVE.B streamMode(A1),alphaMode(A6);save alpha mode in stack frame
SUB #16,SP ;make room on stack for results and first error ; <SM4>.start
PEA backStream(A1)
PEA 12(SP)
PEA foreStream(A1)
PEA 12(SP)
_StreamToMask
_StreamToMask
MOVE.L (SP)+,D0 ;get alpha mask
MOVE.L (SP)+,D4 ;get alpha fore color
CMP.W #srcXor,D5 ;are we xoring?
BNE.S @2 ;no, use normal default mask
MOVE.L D4,D0 ;yes, use alpha fore color as alpha mask
@2: MOVE.L D0,alphaFore(A6) ;save alpha mask
ADDQ #4,SP ;throw away background mask
MOVE.L (SP)+,D5 ;get alpha back color
MOVEQ #0,D2 ;clear out alpha mask
MOVE.B alphaMode(A6),D0 ;get alpha again
BNE.S @3 ;if non-zero, use that value
MOVEQ #3,D0 ;if zero, draw to both
@3: BTST #1,D0 ;are we drawing to graphics?
BEQ.S @4 ;no, skip
OR.L alphaFore(A6),D2 ;yes, add alpha bits to mask
OR.L D4,D6 ;apply alphaFgColor to the foreground color
OR.L D5,D7 ;apply alphaBkColor to the background color
@4: BTST #0,D0 ;is the alpha going to be drawn?
BEQ.S @5 ;no, then don't apply alpha to fg,bk colors
OR.L alphaBack(A6),D2 ;yes, add graphic bits to mask
@5: MOVE.L D2,alphaMask(A6) ;save alpha mask in stack frame
NOT.L D2 ;check for mask of all ones
SNE alphaMode(A6) ;if mask of all ones, set alphamode to true
@noalpha
; <17> End of alpha channel changes
MOVE COLRBIT(A2),D2 ;GET COLOR BIT SELECT
MOVEQ #-1,D4 ;DEFAULT VALUE FOR FGLONG
MOVEQ #0,D5 ;DEFAULT VALUE FOR BKLONG
; IF IT IS AN OLD PORT, AND WE ARE GOING TO THE SCREEN, THEN DON'T DO
; SEPARATION, JUST MAP PLANAR COLOR VALUES INTO COLOR INDICES.
; IF IT IS A NEW PORT, DON'T NEED TO REMAP THE VALUES (UNLESS ONE BIT DEEP).
; if pattern mode and new pattern, leave black and white
MOVE D3,D0 ;copy the mode
BCLR #3,D0 ;clear pattern bit
; not necessary since d1 already has pattern bit
; SNE D1 ;remember that the pattern bit was set
; CMP #$32,D0 ;is it hilite? <•••>
; BEQ COLOROK ;if so, use black/white <•••>
CMP #srcXor,D0 ;is it srcXor or patXor?
BEQ COLOROK ;if so, use black/white
CMP #notSrcXor,D0 ;is it notSrcXor or notPatXor?
BEQ COLOROK ;if so, use black/white
TST.B D1 ;IS IT A PATTERN MODE?
BEQ.S DestBitMap ;if not skip, otherwise check if its a multibit pattern <08JUNE92 SAH>
ISPAT TST.B NEWPATTERN(A6) ;FLAG TRUE IF DESTINATION IS PIXMAP
BEQ.S DestBitMap ;=>YES, GET COLOR PIXEL MASKS
MOVE.L LOCPAT(A6),A0 ;GET PATTERN POINTER
MOVE.L (A0),A0 ;GET HANDLE TO PATTERN
MOVE.L (A0),A0 ;GET POINTER TO PATTERN
TST PATTYPE(A0) ;WHAT TYPE OF PATTERN IS IT?
BNE COLOROK ;=>A NEW ONE, BLACK FG & WHITE BK
DestBitMap
;here src is either an old pattern or image data
TST PORTBITS+ROWBYTES(A2) ;old port or new?
BPL.S REMAP ;if old, go check color bit
CMP #2,DSTPIX+PIXELSIZE(A6) ;worry about fg remapping?
BGT.S REP ;if 4 or 8 bit, just replicate the pixel
CMP.L D6,D7 ;is the fg color the same as the bk color?
BNE.S REP ;if not, no conflict; just replicate the pixel
; If the source RGBs are identical, dont change the foreground. But, if they started out
; different, and they mapped to be the same thing, then flip (invert) the foreground color.
LEA RGBFgColor(A2),A0 ;get the forecolor RGB from the port
LEA RGBBkColor(A2),A1 ;and get the backcolor as well
CMP.L (A0)+,(A1)+ ;if the R or G are not equal, flip the back color
BNE.S @goOnAndFlip
CMP (A0)+,(A1)+ ;if R, G and B are equal, dont flip the back color
BEQ.S REP
@goOnAndFlip
tst d2 ;color bit set? <1.6> BAL
bne.s rep ;yes, fg=bk is ok <1.6> BAL
LEA RGBFgColor(A2),A0 ;get the forecolor RGB from the port
SUBQ #6,SP ;make room for the color
MOVE.L SP,A1 ;set up as destination
MOVE.L (A0)+,(A1)+ ;copy R, G to stack
MOVE (A0)+,(A1)+ ;copy B to stack
MOVE.L SP,-(SP) ;push the copy of the forecolor RGB
_InvertColor ;get the furthest thing from it
SUBQ #4,SP ;make room for the function result
PEA 4(SP) ;push the inverted RGB
_Color2Index ;get its index
MOVE.L (SP)+,D6 ;and put it in the forecolor register
ADDQ #6,SP ;throw away the color placeholder
BRA.S REP ;now the foreground, background longs can be made
REMAP TST D2 ;GET COLOR BIT SELECT
BMI COLOROK ;COLRBIT NEG MEANS NO COLOR
BNE.S REMAP2 ;=>DOING PLANES, DO OLD WAY
CMP #1,DSTPIX+PIXELSIZE(A6) ;IS PIXELSIZE 1?
BEQ.S remapOld1bit ;=>yes, REMAP COLORS FOR old 1-bit pixels
MOVE.L D7,D0 ;GET BKCOLOR (xxIC MYBr gbwb)
BSR mapToColor
MOVE.L D0,D7 ;get mapped back color
MOVE.L D6,D0 ;GET FGCOLOR (xxIC MYBr gbwb)
BSR mapToColor
MOVE.L D0,D6 ;get mapped fore color
; REPLICATE THE RETURNED COLOR THROUGHOUT THE LONG
REP MOVE DSTPIX+PIXELSIZE(A6),D0 ;GET THE SIZE OF THE PIXEL
cmp #1,d0
beq.s DoOneBit
MOVE.L D6,D4 ;COPY FG PIXEL
MOVE.L D7,D5 ;COPY BK PIXEL
MOVEQ #32,D1 ;GET SIZE OF A LONG
NXTPXL SUB D0,D1 ;SAY WE'VE DONE A PIXEL
BLE.S COLOROK ;=>IT WAS THE LAST ONE
LSL.L D0,D4 ;PREPARE FOR NEXT FG PIXEL
LSL.L D0,D5 ;PREPARE FOR NEXT BK PIXEL
OR.L D6,D4 ;INSTALL FG PIXEL
OR.L D7,D5 ;INSTALL BK PIXEL
BRA.S NXTPXL ;=>DO ENTIRE LONG
DoOneBit
LSR.L #1,D6 ;if 1-bit, fg and bk end up as 0 or -1
SUBX.L D4,D4 ;note that this ignores whatever is in the other
LSR.L #1,D7 ; 31 bits incase someone (like the standard MBDF)
SUBX.L D5,D5 ; puts -1 instead of 1 in forecolor.
bra.s COLOROK
; From here to COLOROK, the port is old, the destination is 1 bit, the modes are old
remapOld1bit ;Special case colorbit is zero
btst #0,d6
bne.s @fgOK
moveq #0,d4
@fgOK
btst #0,d7
beq.s ColorOK
moveq #-1,d5
bra.s ColorOK
REMAP2 MOVEQ #3,D0 ;MASK FOR BOTTOM 2 BITS
AND D3,D0 ;GET 2 BITS OF MODE
BEQ.S COPY ;BR IF COPY MODE
;
; THE XOR MODES DEPEND ON NEITHER FOREGROUND OR BACKGROUND COLOR
;
CMP #2,D0 ;IS IT SOME KIND OF XOR ?
BEQ.S COLOROK ;YES, THEY DON'T CHANGE
BGT.S BICMODE ;BRANCH IF BIC
;ELSE MUST BE OR
;
; THE OR MODES DEPEND ONLY ON THE FOREGROUND COLOR
;
ORMODE MOVE.L D6,D1 ;GET FOREGROUND COLOR
SHARE BTST D2,D1 ;TEST FOREGROUND COLOR BIT
BNE.S COLOROK ;NO CHANGE IF FG TRUE
EOR #2,D3 ;ELSE INVERT MODE BIT 2
BRA.S NEWMODE ;UPDATE MODE AND QUIT
;
; THE BIC MODES DEPEND ONLY ON THE BACKGROUND COLOR
;
BICMODE MOVE.L D7,D1 ;GET BACKGROUND COLOR
NOT.L D1 ;INVERT IT
BRA SHARE ;AND SHARE CODE
;
; THE COPY MODES DEPEND ON BOTH FOREGOUND AND BACKGROUND
;
COPY MOVE.L D6,D0 ;GET FOREGROUND COLOR
MOVE.L D7,D1 ;GET BACKGROUND COLOR
BTST D2,D0 ;TEST FOREGROUND COLOR BIT
BEQ.S FORE0 ;BRANCH IF IT'S ZERO
FORE1 BTST D2,D1 ;TEST BACKGROUND COLOR BIT
BEQ.S COLOROK ;NO CHANGE IF BKGND FALSE
MOVEQ #8,D3 ;ELSE REPLACE MODE = PAT COPY
USEPAT MOVE.L GRAFGLOBALS(A5),A0 ;GET GLOBAL POINTER
LEA BLACK(A0),A0 ;POINT TO BLACK PATTERN
MOVE.L A0,LOCPAT(A6) ;REPLACE PATTERN WITH BLACK
SF NEWPATTERN(A6) ;AND SET NEWPATTERN FALSE
BRA.S NEWMODE ;UPDATE MODE AND QUIT
FORE0 BTST D2,D1 ;TEST BACKGROUND COLOR BIT
BNE.S INVMODE ;IF BK TRUE, INVERT MODE
MOVEQ #12,D3 ;ELSE REPLACE MODE = NOTPAT COPY
BRA.S USEPAT ;AND PATTERN WITH BLACK
INVMODE EOR #4,D3 ;USE INVERSE OF MODE <HACK>
NEWMODE MOVE D3,LOCMODE(A6) ;CHANGE INPUT MODE
COLOROK MOVE.L D4,FCOLOR(A6) ;RETURN EXTENDED PIXEL
MOVE.L D5,BCOLOR(A6) ;RETURN EXTENDED PIXEL
BTST #5,D3 ;is it an arithmetic mode?
BEQ noArith ;no arithmetic inputs to set up
MOVE DSTPIX+PIXELSIZE(A6),D7 ;GET THE SIZE OF THE PIXEL
MOVE.L bkColor(A2),D5 ;get the background color
TST PORTBITS+ROWBYTES(A2) ;OLD OR NEW GRAFPORT?
BMI.S setOpColor ;new grafPort, use fields in port
; check mode to see if new arithmetic mode in old port
; if so, set up pin and weight to default values
; add with pin default pin is white
; sub with pin default pin is black
; blend default weight is 50% gray
MOVE.L D5,D0 ;pass background color to mapToColor
BSR mapToColor ;turn the old QD bits into a color long
MOVE.L D0,D5 ;save it for later
LEA HiliteRGB,A2 ;get hilite color from low memory
MOVEQ #$07,D0 ;arithmetic mode variants 0 … 7
AND D3,D0 ;get masked mode
SUBQ #1,D0 ;less add with pin variant
BEQ.S @setWhite ;if add with pin, set to white
BMI.S @setGray ;if average, set to gray
LEA xrgbBlack,A0 ;point to black
BRA.S setUpPinWeight
@setWhite
LEA xrgbWhite,A0 ;point to white
BRA.S setUpPinWeight
@setGray
LEA xrgbGray,A0 ;point at gray
BRA.S setUpPinWeight
setOpColor
; set up pin, weight rgbs for modes max, min, and avg
; set up weights complement for average
; note that rgb in pin & notWeight are in reverse order from source
MOVE.L ([grafVars,A2]),A0 ;point to weight value
LEA 6(A0),A2 ;point to hilite color
; Set up locals in A6 for arithmetic modes in bltBlt, rgnBlt, drawSlab, stretch
setUpPinWeight
MOVEQ #2,D1 ;do three times
LEA pin+6(A6),A1 ;word past last pin value
LEA notWeight+6(A6),A3 ;word past last not weight value
@nextPin
MOVE (A0)+,D0 ;get red components of pin, weight
BNE.S @notZero ;if input is zero, change it to 1
MOVEQ #1,D0 ;so that complement will be -1 (FFFF)
@notZero
MOVE D0,-(A1) ;save red as is for pin, weight
NEG D0 ;flip for complement of weight
MOVE D0,-(A3) ;save red destination weight
DBRA D1,@nextPin
SUBQ #6,SP ;make room for the color
SUBQ #4,SP ;space for function result
MOVE.L A2,-(SP) ;pass pointer to hilite color
_Color2Index ;leave pixel on stack (hilite color)
CMP.L (SP),D5 ;same as the background?
BNE.S @notSame
LEA 4(SP),A1
MOVE.L A2,A0
MOVE.L (A0)+,(A1)+ ;copy R, G to stack
MOVE (A0)+,(A1)+ ;copy B to stack
PEA 4(SP) ;push the copy of the background RGB
_InvertColor ;get the furthest thing from it
PEA 4(SP) ;pass pointer to hilite color
_Color2Index ;leave pixel on stack (hilite color)
@notSame
; set up pointers to color table, inverse color table and table resolution in locals
MOVE.L ([theGDevice]),A0 ;get a pointer to the current device
MOVE.L ([GDPMap,A0]),A1 ;get pixMap's handle
MOVE.L ([GDITable,A0]),A0 ;get the inverse color table's master pointer
MOVE ITabRes(A0),D0
MOVE D0,invSize(A6) ;save resolution of inverse color table
MOVEQ #16,D1
SUB D0,D1
MOVE D1,rtShift(A6) ;set up for Average, how far to shift mulu result
move.l a0,d0
_rTranslate24To32 ;strip high byte @@@@ BAL
MOVE.L d0,invColor(A6) ;save pointer to inverse color table
MOVE.L ([PMTable,A1]),A1 ;pointer to color table
LEA ctTable+rgb+red(A1),A1 ;location of "red" of first color in color table
move.l a1,d0
_rTranslate24To32 ;strip high byte @@@@ BAL
MOVE.L d0,colorTable(A6) ;save a pointer to the device colortable
MOVE.L D5,D2 ;COPY BK PIXEL
MOVE.L (SP),D4 ;copy of hilite pixel
;note that were comparing against the port background (which may not be the drawing background)
MOVEQ #32,D1 ;GET SIZE OF A LONG
@nxtPixel
SUB D7,D1 ;SAY WE'VE DONE A PIXEL
BLE.S @done ;=>IT WAS THE LAST ONE
LSL.L D7,D2 ;PREPARE FOR NEXT BK PIXEL
OR.L D5,D2 ;INSTALL BK PIXEL
LSL.L D7,D4 ;shift hilite pixel up a notch
OR.L (SP),D4 ;add in a pixel to the low order pixel position
BRA.S @nxtPixel
@done
MOVE.L D2,transColor(A6) ;save for transparent
MOVE.L D4,hilitColor(A6) ;save for hilite
ADD #10,SP ;throw away hilite pixel, rgb inverse
noArith
MOVEM.L (SP)+,D3-D7/A2-A3 ;RESTORE REGS
; UNLK A4 ;DONE WITH STACK FRAME
RTS ;JUST RETURN
; GET COLORS FROM PORT AND MAP FOR PROPER DEPTH
; MAP THE RGB IN THE OLD-STYLE COLOR INTO A NEW COLOR INDEX
; KEEP INTENSITY IN BIT 9.
; THE BITS IN THE OLD STYLE COLORS ARE IN THE ORDER:
; BIT 0: BK/FG BIT (0 IF WHITE, ELSE 1)
; BIT 1: NOT BK/FG BIT (1 IF WHITE, ELSE 0)
; RGB BITS
; BIT 2: NOT BLUE
; BIT 3: NOT GREEN
; BIT 4: NOT RED
; CMY BITS
; BIT 5: BLACK BIT
; BIT 6: YELLOW BIT
; BIT 7: MAGENTA BIT
; BIT 8: CYAN BIT
; INTENSITY BIT
; BIT 9: 0 = FULL INTENSITY, 1 = HALF INTENSITY
mapToColor
LSR #1,D0 ;CHECK FOR WHITE (I CMYB rgbw)
BCS.S @0 ;=>NOT WHITE
OR #$00E0,D0 ;ELSE SET WHITE BITS (CMY = 111)
@0 LSR #5,D0 ;SHIFT ICMY INTO LOW NIBBLE
AND #$7,D0 ;CLEAR ALL BUT LOW NIBBLE
MOVE.L QDColors,A0 ;GET DEFAULT COLORS
MOVE.L 4(A0,D0*8),-(SP) ;PUSH GREEN, BLUE
MOVE.W 2(A0,D0*8),-(SP) ;PUSH RED
CLR.L -(SP) ;MAKE ROOM FOR FUNCTION RESULT
PEA 4(SP) ;POINT TO VAR RGB
_COLOR2INDEX ;CONVERT IT TO AN INDEX
MOVE.L (SP)+,D0 ;GET MAPPED COLOR
ADDQ #6,SP ;STRIP COLORSPEC
RTS
xrgbBlack DC.W $0000,$0000,$0000 ;BLACK
xrgbWhite DC.W $FFFF,$FFFF,$FFFF ;WHITE
xrgbGray DC.W $7FFF,$7FFF,$7FFF ;GRAY
;----------------------------------------------------------------
;
; Dispatcher for alpha channel utility routines (Trap $ABC0)
; Added in revision <17>.
;
; as seen in QDciPatchROM.a <sm 6/9/92>stb
AlphaDispatch PROC EXPORT
IMPORT RSetHSize
JMP @dispatch(PC,D0.W*4)
@dispatch
BRA.W AlphaVersion
BRA.W SetForeStream
BRA.W SetForeTransparency
BRA.W SetBackStream
BRA.W SetBackTransparency
BRA.W GetForeStream
BRA.W GetForeTransparency
BRA.W GetBackStream
BRA.W GetBackTransparency
BRA.W ResizeGrafVars
BRA.W GetStreamMode
;
; FUNCTION AlphaVersion:INTEGER;
;
AlphaVersion
MOVE.W #$0100,4(SP) ;return version 1.0
RTS
;
; PROCEDURE SetForeStream(streamID: LongInt);
; PROCEDURE SetBackStream(streamID: LongInt);
;
SetForeStream
MOVEQ #foreStream,D1 ;point at foreStream/foreRatio in grafvars
BRA.S SetStream ;jump into common code
SetBackStream
MOVEQ #backStream,D1 ;point at backStream/backRatio in grafvars
SetStream
BSR.S SetSub
BEQ.S @exit
MOVE.L 4(SP),(A0) ;move stream from stack to grafvars
@exit RTD #4 ;clean off stack and return
;
; PROCEDURE SetForeTransparency(streamRatio: INTEGER);
; PROCEDURE SetBackTransparency(streamRatio: INTEGER);
;
SetForeTransparency
MOVEQ #foreRatio,D1 ;point at foreStream/foreRatio in grafvars
BRA.S SetTrans ;jump into common code
SetBackTransparency
MOVEQ #backRatio,D1 ;point at backStream/backRatio in grafvars
SetTrans
BSR.S SetSub
BEQ.S @exit
MOVE.W 4(SP),(A0) ;move ratio from stack to grafvars
@exit RTD #2 ;clean off stack and return
SetSub MOVE.L grafGlobals(A5),A0 ;point to QuickDraw globals
MOVE.L thePort(A0),A0 ;get pointer to current port
TST portBits+rowBytes(A0) ;new port?
BPL.S @exit ;no, then don't access grafVars
MOVE.L grafVars(A0),D0 ;get grafVars handle from port
BEQ.S @exit ;if null, exit
MOVE.L D0,A0 ;move grafvars handle to more useful register
MOVE.L (A0),A0 ;deref it
BTST #PmNewGVBit-8,pmFlags(A0) ;check for new grafvars flag
BNE.S @1 ;if it was set, no need to grow grafvars
MOVE.L D0,-(SP) ;save grafvars handle
MOVE.L D0,-(SP) ;push grafvars handle for resize call
_ResizeGrafVars ;grow grafvars to new size
MOVE.L (SP)+,A0 ;restore grafvars handle
MOVE.L (A0),A0 ;deref it again
@1: ADD.W D1,A0 ;bump to field being modified
ST D0 ;set do it flag to true
RTS
@exit CLR D0 ;set do it flag to false
RTS
;
; PROCEDURE GetForeStream: INTEGER;
; PROCEDURE GetBackStream: INTEGER;
;
GetForeStream
MOVEQ #foreStream,D1 ;point at foreStream in grafvars
BRA.S GetStream ;jump into common code
GetBackStream
MOVEQ #backStream,D1 ;point at backStream in grafvars
GetStream
MOVE.L grafGlobals(A5),A0 ;point to QuickDraw globals
MOVE.L thePort(A0),A0 ;get pointer to current port
TST portBits+rowBytes(A0) ;new port?
BPL.S @default ;no, then don't access grafVars
MOVE.L grafVars(A0),D0 ;get grafVars handle from port
BEQ.S @default ;if null, return default info
MOVE.L D0,A0 ;move grafvars handle to more useful register
MOVE.L (A0),A0 ;deref it
BTST #PmNewGVBit-8,pmFlags(A0) ;check for new grafvars flag
BEQ.S @default ;if it was clear, return default info
ADD.W D1,A0 ;bump to either foreStream or backStream
MOVE.L (A0),4(SP) ;move stream from grafvars to user variable
RTS
@default
CLR.L 4(SP) ;move default stream to user variable
RTS
;
; PROCEDURE GetForeTransparency: INTEGER;
; PROCEDURE GetBackTransparency: INTEGER;
;
GetForeTransparency
MOVEQ #foreRatio,D1 ;point at foreRatio in grafvars
BRA.S GetTrans ;jump into common code
GetBackTransparency
MOVEQ #backRatio,D1 ;point at backRatio in grafvars
GetTrans
MOVE.L grafGlobals(A5),A0 ;point to QuickDraw globals
MOVE.L thePort(A0),A0 ;get pointer to current port
TST portBits+rowBytes(A0) ;new port?
BPL.S @default ;no, then don't access grafVars
MOVE.L grafVars(A0),D0 ;get grafVars handle from port
BEQ.S @default ;if null, return default info
MOVE.L D0,A0 ;move grafvars handle to more useful register
MOVE.L (A0),A0 ;deref it
BTST #PmNewGVBit-8,pmFlags(A0) ;check for new grafvars flag
BEQ.S @default ;if it was clear, return default info
ADD.W D1,A0 ;bump to either foreStream or backStream
MOVE.W (A0),4(SP) ;move ratio from grafvars to user variable
RTS
@default
CLR.W 4(SP) ;move default ratio to user variable
RTS
;
; On Entry:
; (on stack): grafvars handle
;
; ONLY TRASHES D0/A0
;
ResizeGrafVars
MOVE.L 4(SP),A0 ;get grafVars handle
MOVE.L (A0),A0 ;deref grafvars handle
BSET #PmNewGVBit-8,pmFlags(A0) ;check new grafvars flag and set it if not already
BNE.S @exit ;if it was set, then we are too
MOVE.L 4(SP),A0 ;get grafVars handle agian
MOVE.L #newGrafVarRec,D0 ;get size of new grafvars
BSR RSetHSize ;set the handle to be that size
MOVE.L (A0),A0 ;deref again
LEA foreStream(A0),A0 ;bump to beginning of our stuff
CLR.L (A0)+ ;clear foreStream
CLR.L (A0)+ ;clear foreRatio, half of backStream
CLR.L (A0)+ ;clear half of backStream, backRatio
CLR.W (A0)+ ;clear stream mode and filler
@exit RTD #4 ;all done
;
; On Entry:
; D1: penmode (not necessarily from the current port)
;
; On Exit:
; D1: penmode stripped of alpha transfer bits
;
GetStreamMode
MOVE.L grafGlobals(A5),A0 ;point to QuickDraw globals
MOVE.L thePort(A0),A0 ;get pointer to current port
TST portBits+rowBytes(A0) ;new port?
BPL.S @exit ;no, then don't access grafVars
MOVE.L grafVars(A0),D0 ;get grafVars handle from port
BEQ.S @exit ;if null, exit
MOVE.L D0,-(SP) ;save copy of grafvars handle
MOVE.L D0,-(SP) ;put grafVars handle on stack
_ResizeGrafVars ;make sure grafvars are big enough
MOVE.L (SP)+,A0 ;get grafVars handle off stack
MOVE.L (A0),A0 ;dereference it
MOVE.W D1,D0 ;make copy of penmode
LSR.W #8,D0 ;right align alpha bits
AND.W #3,D0 ;mask off all but alpha bits
MOVE.B D0,streamMode(A0) ;put alphamode into streamMode
@exit AND.W #$FCFF,D1 ;remove alpha bits from penmode
RTS ;return stripped penmode
;
; On Entry:
; (on stack): pointer to streamID and ratio
; (on stack): pointer to where to put
; alphamask (long) and alphacolor (long)
;
StreamToMask PROC EXPORT
MOVE.L 8(SP),A0 ;get pointer to streamID/ratio
MOVE.L 4(SP),A1 ;get pointer to result destination
MOVE.W 4(A0),D0 ;get ratio
TST.L (A0) ;check if stream is graphics (zero)
BEQ.S @1 ;yes, skip
NOT.W D0 ;no, reverse context of transparency
@1: MOVE.W D0,D1
SWAP D0
MOVE.W D1,D0
MOVE.L THEGDEVICE,A0 ;get handle of current gdevice
MOVE.L (A0),A0 ;deref it
MOVE.L gdPMap(A0),A0 ;get handle of gdevice's pixmap
MOVE.L (A0),A0 ;deref it
MOVE.W pmPixelSize(A0),D1 ;get its pixel size
CMP #16,D1 ;is it 16-bits per pixel?
BEQ.S @16bits
MOVE.L MaskBC,D1 ;get 32-bits per pixel not mask
BRA.S @2
@16bits MOVE.L #$7FFF7FFF,D1 ;get 16-bits per pixel not mask
@2: NOT.L D1 ;reverse the mask
AND.L D1,D0 ;mask alpha color
MOVE.L D1,(A1)+ ;save alphamask
MOVE.L D0,(A1)+ ;save alphacolor
RTD #8
GetCPixel FUNC EXPORT
EXPORT GETPIXEL
IMPORT HideCursor,ShowCursor,PortToMap
;---------------------------------------------------------
;
; FUNCTION GetPixel(h,v: INTEGER): BOOLEAN;
; PROCEDURE GetCPixel(h,v: INTEGER; myColor: RGBColor);
;
; Returns TRUE if the pixel at (h,v) is set to black.
; h and v are in local coords of the current grafport.
;
; WATCH OUT FOR STACK TRICKERY WHEN GETCPIXEL CALLS GETPIXEL!!
;
; CLOBBERS A0,A1,D0,D1,D2
;
; reflect the patch from QDciPatchROM.a so that SwapMMUMode is called <sm 6/9/92>stb
; if the pixmap needs 32-bit addressing (pmVersion = 4). <sm 6/9/92>stb
PARAMSIZE EQU 4
RETURN EQU PARAMSIZE+8 ;ADDRESS OF BOOLEAN/RGBCOLOR
HLOC EQU PARAMSIZE+8-2 ;HORIZONTAL POSITION
VLOC EQU HLOC-2 ;VERTICAL POSITION
VARSIZE EQU 0 ;TOTAL SIZE OF LOCALS
MOVE.L 8(SP),-(SP) ;PUSH H,V
MOVEQ #1,D2 ;ROUTINE = GETCPIXEL
BSR.S SHARE ;USE COMMON CODE
RTD #8 ;STRIP PARAMS AND RETURN
GETPIXEL
MOVEQ #0,D2 ;ROUTINE = GETPIXEL
SHARE LINK A6,#VARSIZE ;ALLOCATE STACKFRAME
MOVEM.L D4-D5/A2-A3,-(SP) ;SAVE WORK REGISTERS
MOVE.L THEGDEVICE,-(SP) ;SAVE CURRENT GRAFDEVICE
MOVE.L GRAFGLOBALS(A5),A0 ;POINT TO QUICKDRAW GLOBALS
MOVE.L THEPORT(A0),A0 ;GET THEPORT
_PORTTOMAP ;GET BIT/PIXMAP IN A0
; GET GLOBAL COORDINATES OF VLOC INTO D4 AND HLOC INTO D5
OLDRB MOVE VLOC(A6),D4 ;GET VERTICAL
SUB BOUNDS+TOP(A0),D4 ;CONVERT TO GLOBAL COORDS
MOVE HLOC(A6),D5 ;GET HORIZ COORD
SUB BOUNDS+LEFT(A0),D5 ;CONVERT TO GLOBAL
; IS IT FROM THE SCREEN?
MOVE.L MAINDEVICE,A2 ;GET MAIN DEVICE
MOVE.L (A2),A2 ;POINT TO IT
MOVE.L GDPMAP(A2),A2 ;GET PIXMAP HANDLE
MOVE.L (A2),A2 ;POINT TO PIXMAP
MOVE.L BASEADDR(A0),D1 ;GET PORT'S BASEADDR
CMP.L BASEADDR(A2),D1 ;SAME AS SCREEN'S?
seq.b -(sp) ;push crsrFlag @@@@ BAL 14Apr88
move.l a0,a3 ;save pixmap in a3
BNE.S NOTSCRN ;=>NO, NOT SCREEN
; IT IS FROM THE SCREEN! Shield the Cursor. @@@@ BAL 14Apr88
MOVE D5,-(SP) ;PUSH GLOBAL LEFT
MOVE D4,-(SP) ;PUSH GLOBAL TOP
MOVE D5,-(SP) ;PUSH GLOBAL RIGHT
MOVE D4,-(SP) ;PUSH GLOBAL BOTTOM
MOVE.L JShieldCursor,A1 ;get lo mem vector
JSR (A1) ;and call it
MOVE.L DEVICELIST,A3 ;GET FIRST IN DEVICE LIST
DONXT MOVE.L (A3),A2 ;POINT TO DEVICE
TST GDFLAGS(A2) ;IS DEVICE ACTIVE?
BPL.S NXTDEV ;=>NO, NOT ACTIVE
LEA GDRECT(A2),A1 ;POINT TO DEVICE'S RECT
CMP (A1)+,D4 ;IS VERTICAL < GDRECT.TOP ? <SMC 18SEP90> <11>
BLT.S NXTDEV ;=>YES, CHECK NEXT DEVICE <SMC 18SEP90> <11>
CMP (A1)+,D5 ;IS HORIZONTAL < GDRECT.LEFT ? <SMC 18SEP90> <11>
BLT.S NXTDEV ;=>YES, CHECK NEXT DEVICE <SMC 18SEP90> <11>
CMP (A1)+,D4 ;IS VERTICAL >= GDRECT.BOTTOM ?
BGE.S NXTDEV ;=>YES, CHECK NEXT DEVICE
CMP (A1)+,D5 ;IS HORIZONTAL >= GDRECT.RIGHT ?
BLT.S GOTDEV ;=>NO, FOUND DEVICE
NXTDEV MOVE.L GDNEXTGD(A2),D0 ;GET HANDLE TO NEXT DEVICE
MOVE.L D0,A3 ;KEEP IN A3
BNE.S DONXT ;=>THERE IS A DEVICE
BRA DONE ;=>DEVICE NOT FOUND, JUST RETURN
; FOUND THE DEVICE! SET DEVICE AND OFFSET POINT TO DEVICE LOCAL COORDINATES
GOTDEV MOVE.L A3,THEGDEVICE ;MAKE DEVICE CURRENT
LEA GDRECT(A2),A1 ;POINT TO DEVICE'S RECT
SUB (A1)+,D4 ;OFFSET VERTICAL
SUB (A1)+,D5 ;OFFSET HORIZONTAL
MOVE.L GDPMAP(A2),A3 ;GET PIXMAP HANDLE
MOVE.L (A3),d0 ;POINT TO PIXMAP
_rTranslate24To32 ;strip off high byte @@@@ BAL 14Apr88
move.l d0,a3
;-----------------------------------------------------------
;
; Switch to 32 bit addressing mode
;
Needs32BitMode
move.b #$ff,(sp) ;flag the fact that MMU mode must be swapped <KON 20JUN90>
moveq #true32b,d0 ;switch to 32 bit addressing
move.w d2,-(sp) ;save color/ bw flag across call
_rSwapMMUMode ;get previous mode in d0.b (can trash a0/a2, d0/d2)
move.w (sp)+,d2 ;restore flag in d2
;save previous state in d0 for later
bra.s MMUModeOK
NOTSCRN
;
; Check if pixmap needs 32-bit addressing <KON 20JUN90>
;
baseAddr32Bit EQU 2
tst.w rowbytes(a3) ; <KON 20JUN90>
bpl.s MMUModeOK ;it's a bitmap <KON 20JUN90>
btst #baseAddr32Bit,pmVersion+1(a3) ; <KON 20JUN90>
bne.s Needs32BitMode ;pixmap needs 32-bit addressing <KON 20JUN90>
MMUModeOK
MOVE ROWBYTES(A3),D1 ;GET ROWBYTES
AND #nuRBMask,D1 ;AND MASK OFF FLAG BITS
MULU D4,D1 ;CALC VERT * ROWBYTES
MOVE.L BASEADDR(A3),A1 ;GET BASEADDR
ADD.L D1,A1 ;ADD VERTICAL OFFSET
MOVEQ #1,D1 ;ASSUME PIXELSIZE = 1
TST ROWBYTES(A3) ;NEW PIXMAP?
BPL.S OLDMAP ;=>NO, USE PIXSIZE = 1
MOVE PIXELSIZE(A3),D1 ;ELSE GET TRUE PIXELSIZE
OLDMAP MULU D1,D5 ;PIXEL OFFSET = PIXELSIZE*HLOC
BFEXTU (A1){D5:D1},D4 ;EXTRACT THE PIXEL
tst.b (sp)
beq.s @noSwap ;need to swap modes again?
;previous MMU state still in d0
move.l d2,d5 ;protect flag in d5
_rSwapMMUMode ;get previous mode in d0.b (can trash a0/a2, d0/d2)
move.l d5,d2 ;restore flag
@noSwap TST D2 ;COLOR OR NOT?
BEQ.S NOCOLOR ;=>NO COLOR
MOVE.L D4,-(SP) ;PUSH INDEX
MOVE.L RETURN+4(A6),-(SP) ;POINT TO RGBCOLOR
_INDEX2COLOR ;CONVERT THE INDEX TO A COLOR
BRA.S DONE ;=>RESTORE CURSOR AND RETURN
NOCOLOR cmp.w #16,pixelType(a3) ;direct device?
bne.s @clut ;no, don't hack pixel value
tst.l d4 ;is it all zeros?
seq d4 ;yes, flag black
bra.s @ret
@clut TST D4 ;ELSE TEST PIXEL
SNE D4 ;SET BOOLEAN RESULT
@ret NEG D4 ;MAKE $FF --> $01
MOVE.B D4,RETURN(A6) ;AND RETURN IT
DONE tst.b (sp)+ ;pop and check crsrFlag
beq.s @noShow ;need to show cursor?
_SHOWCURSOR ;show it
@noShow MOVE.L (SP)+,THEGDEVICE ;RESTORE CURRENT GRAFDEVICE
MOVEM.L (SP)+,D4-D5/A2-A3 ;RESTORE WORK REGISTERS
UNLINK PARAMSIZE,'GETCPIXEL'
Translate24To32 PROC EXPORT ;BAL 26Dec88
IF forROM THEN ; SuperMario is 32 bit only ROM
RTS
ELSE
;-------------------------------------------------------
;
; FUNCTION Translate24To32(Addr24:long) : Addr32;
;
; Translate a 24 Bit address to a valid 32 Bit address.
; (Will be toolbox trap $AB03)
;
; INPUT D0=Addr24;
; OUTPUT D0=Addr32;
;
; All registers preserved
;
; Translation algorithm from Mac Family Hardware Reference Table 17-1:
;
; Old first 3 nibbles New first 3 nibbles
; ------------------- -------------------
; xx0 000
; : :
; xx7 007
; xx8 400-->408 for safety in 24 bit mode; also since the emulator doesn't alias
; xx9 F90
; : :
; xxE FE0
; xxF 500
;
;
;
; NOTE: Unlike _StripAddress, this routine does not necessarily
; return an address which can also be used in 24 bit mode.
; Furthermore, Translate24To32 can not be called meaningfully
; with the result of a previous translation.
;
;
AND.L Lo3Bytes,D0 ;Clean high byte for fast exit
BCLR #23,D0 ;Is the address in RAM?
BNE.S @NotRam ;no, go patch up address
RTS ;quick exit
@NotRam
MOVE.W D1,-(SP) ;Save a work register
MOVE.W #12,D1 ;prepare for shift and clear our word, Scotty
ROL.L D1,D0 ;get 3rd nibble
MOVE.B D0,D1 ;keep for indexing
beq.s @inROM ;handle ROM case for emulator
LSR.L #4,D0 ;clear out 3rd nibble
MOVE.B (TRANSLATE,PC,D1.W),D0 ;compute new high byte
MOVE.W (SP)+,D1 ;Restore work register
ROR.L #8,D0 ;reposition high byte
RTS
@inROM
or.w #$0408,d0 ;set up ROM address
ROR.L #4,D0 ;restore address
ROR.L #8,D0 ;restore address
MOVE.W (SP)+,D1 ;Restore work register
RTS
TRANSLATE
DC.B $40,$F9,$FA,$FB,$FC,$FD,$FE,$50
ENDIF ; forROM
ElsieTranslate24To32 PROC EXPORT ;JJ&BA 2/23/90
IF forROM THEN ; SuperMario is 32 bit only ROM
RTS
ELSE
;-----------------------------------------------------------------------------------------
;
; FUNCTION ElsieTranslate24To32(Addr24: long): Addr32;
;
; Translate an Elsie 24-bit address to a valid Elsie 32-bit address.
;
; INPUT D0=Addr24;
; OUTPUT D0=Addr32;
;
; All other registers preserved
;
; Translation algorithm from Elsie Hardware ERS:
;
; High 3 nibbles (24) High 3 nibbles (32)
; ------------------- -------------------
; xx0 000 (RAM)
; : : :
; xx9 009 (RAM)
; -------------------------------------------
; xxA 40A (ROM)
; : : :
; xxD 40D (ROM)
; -------------------------------------------
; xxE FE0 (Direct Slot)
; xxF 50F (I/O Space)
;
; NOTE: Unlike _StripAddress, this routine does not necessarily
; return an address which can also be used in 24 bit mode.
; Furthermore, Translate24To32 can not be called meaningfully
; with the result of a previous translation.
;
AND.L Lo3Bytes,D0 ;Clean high byte for fast exit
BCLR #23,D0 ;Is the address in lower 8 MB of RAM?
BNE.S @LOOKUP ;no, go patch up address
RTS ;quick exit
@LOOKUP MOVE.W D1,-(SP) ;save a work register
SWAP D0 ;get relevant nibbles into low word
MOVE.W D0,D1 ;...and into index register
LSR.W #4,D1 ;move nibble 3 to use as index
ADD.W (@TABLE,PC,D1.W*2),D0 ;translate by adding table value
SWAP D0 ;move translated nibbles back to high word
MOVE.W (SP)+,D1 ;restore work register
RTS
@TABLE DC.W $0080,$0080,$4080,$4080,$4080,$4080,$FDA0,$5080
ENDIF ; forROM
StuffHex PROC EXPORT
;-------------------------------------------------------
;
; PROCEDURE STUFFHEX(THINGPTR: WORDPTR; S: STR255);
;
; CONVENIENCE ROUTINE TO STUFF HEX INTO ANY VARIABLE.
; BEWARE, NO RANGE-CHECKING.
;
MOVE.L 4(SP),A0 ;A0:=ADDR OF STRING
MOVE.L 8(SP),A1 ;A1:=THINGPTR
MOVE.L (SP),8(SP) ;CLEAN OFF STACK
ADD #8,SP ;POINT TO RETURN ADDR
MOVE.B (A0)+,D2 ;GET STRING LENGTH
AND #$00FE,D2 ;TRUNCATE LENGTH TO EVEN
BEQ.S ENDHEX ;QUIT IF LENGTH = 0
HEXLOOP BSR.S NEXTHEX ;GET HEX DIGIT AND CONVERT TO BINARY
MOVE.B D0,D1 ;SAVE MOST SIG DIGIT
BSR.S NEXTHEX ;GET HEX DIGIT AND CONVERT TO BINARY
LSL.B #4,D1 ;SHIFT MOST SIG INTO PLACE
ADD.B D0,D1 ;FILL IN LS NIBBLE
MOVE.B D1,(A1)+ ;STUFF BYTE INTO THING
SUB #2,D2 ;2 LESS CHARS TO GO
BNE.S HEXLOOP ;LOOP FOR STRING LENGTH
ENDHEX RTS ;RETURN TO PASCAL
;
; LOCAL ROUTINE TO GET NEXT HEX DIGIT AND CONVERT ASCII TO BINARY
;
NEXTHEX MOVE.B (A0)+,D0 ;GET HEX DIGIT FROM STRING
CMP.B #$39,D0 ;IS IT GTR THAN '9' ?
BLE.S SMALL ;NO, DO IT
ADD.B #9,D0 ;YES, ADD CORRECTION
SMALL AND.B #$F,D0 ;TREAT MOD 16, EVEN LOWER CASE OK
RTS
XorSlab PROC EXPORT
;-----------------------------------------------------------
;
; LOCAL PROCEDURE XorSlab(bufAddr: Ptr; left,right: INTEGER);
;
; Enter with:
;
; A0: bufAddr
; D0: pixelShift
; D3: left coord
; D4: right coord
;
; Clobbers: A0,D0,D1,D3,D4,D5,D6
;
; Calc bitcount. If <= 32 then use single BFCHG
ext.l d4 ; clear out high word
ext.l d3 ; ditto
LSL.l D0,D4 ; convert left pixel to left bit
LSL.l D0,D3 ; convert right pixel to right bit
MOVE.l D4,D0 ; get right edge
SUB.l D3,D0 ; get bitcount (right-left)
BLE.S DONE ; => none to do
CMP.l #32,D0 ; BFCHG can only do 32 bits
BGT.S NOTIN1 ; => slab > 32 bits
BFCHG (A0){D3:D0} ; XOR from left to right
DONE RTS ; and return
; calc left field, right field, and number of longs in middle
NOTIN1 MOVEQ #$1F,D1 ; get useful value
MOVE D3,D0 ; get a copy of left edge
AND D1,D0 ; get left edge mod 32
MOVEQ #-1,D5 ; fill leftmask with ones
LSR.L D0,D5 ; D5 = LEFTMASK
MOVE D4,D0 ; get a copy of right edge
AND D1,D0 ; get right edge mod 32
MOVEQ #-1,D6 ; fill rightmask with ones
LSR.L D0,D6 ; shift in 0's from left
NOT.L D6 ; D6 = RIGHTMASK
ASR.l #5,D3 ; convert left dots to longs
ASR.l #5,D4 ; convert right dots to longs
SUB D3,D4 ; LONGCOUNT = rightlong-leftlong
SUBQ #1,D4 ; get longcount-1 for DBRA
LSL #2,D3 ; convert left to bytes
ADD D3,A0 ; add to bufAddr
; do the left, the middle, then the right part of the slab
EOR.L D5,(A0)+ ; XOR the left part of the slab
BRA.S TEST ; see if there is a middle one
NXTLONG NOT.L (A0)+ ; do a middle long
TEST DBRA D4,NXTLONG ; any longs left?
EOR.L D6,(A0) ; XOR the right part of the slab
RTS
DrawSlab PROC EXPORT
EXPORT SlabMode,FastSlabMode
EXPORT slMASK8,slMASK9,slMASK10,slMASK11,slXMASK8,slXMASK9,slXMASK10,slXMASK11
EXPORT slAvg,slAddPin,slAddOver,slSubPin,slTransparent,slMax,slSubOver,slMin,slHilite
EXPORT slArith16Tab,slArith32Tab
;--------------------------------------------------------------
;
; LOCAL PROCEDURE DRAWSLAB
;
; INPUTS:
;
; D0: shift/scratch A0:
; D1: left A1: DSTLEFT, clobbered
; D2: right A2: RGNBUFFER, clobbered
; D3: scratch A3: MINRECT
; D4: FGCOLOR A4: MODECASE
; D5: BKCOLOR A5:
; D6: PATTERN A6: SHARED STACKFRAME
; D7: A7: stack
;
; CLOBBERS: D0-D3,A0,A1,A2
;
; CLIP LEFT AND RIGHT TO MINRECT:
;
; CALLED BY DRAWARC AND DRAWLINE
;
; HERE ARE THE SHARED LOCALS FOR THOSE ROUTINES:
;--------------------------------------------------------------
&CurFile SETC 'DRAWSLAB'
INCLUDE 'DrawingVars.a'
;--------------------------------------------------------------
CMP LEFT(A3),D1 ;IS LEFT < MINRECT.LEFT ?
BGE.S LEFTOK ;NO, CONTINUE
MOVE LEFT(A3),D1 ;YES, LEFT := MINRECT.LEFT
LEFTOK CMP RIGHT(A3),D2 ;IS RIGHT > MINRECT.RIGHT ?
BLE.S RIGHTOK ;NO, CONTINUE
MOVE RIGHT(A3),D2 ;YES, RIGHT := MINRECT.RIGHT
RIGHTOK CMP D2,D1 ;IS LEFT >= RIGHT ?
BGE.S DONESLAB ;YES, QUIT
; GOT LEFT AND RIGHT, CONVERT PIXELS TO BITS
ext.l d1 ;compute result in a long <BAL 15Sep88>
ext.l d2 ;compute result in a long <BAL 15Sep88>
LSL.l D0,D1 ;CONVERT LEFT PIXELS TO BITS
move.l d1,slabLeft(a6) ;copy for below, arith setup <BAL 17Jan89>
LSL.l D0,D2 ;CONVERT RIGHT PIXELS TO BITS
; SET UP LEFTMASK AND RIGHTMASK
MOVEQ #$1F,D0 ;NEED RIGHT MOD 32
AND D0,D1 ;GET LEFT MOD 32
MOVEQ #-1,D3 ;GET ONES INTO D3
LSR.L D1,D3 ;GET LEFTMASK IN D3
AND D2,D0 ;GET RIGHT MOD 32
MOVEQ #-1,D1 ;GET ONES INTO D1
LSR.L D0,D1 ;GET LEFTMASK IN D1
NOT.L D1 ;TURN INTO A RIGHTMASK
MOVE.l slabLeft(a6),D0 ;GET LEFT IN D0 <BAL 15Sep88>
;
; CALC WORDCOUNT, DSTPTR, MASKPTR, AND TAKE CASE JUMP
;
ASR.l #5,D2 ;CONVERT RIGHT TO LONGS <BAL 15Sep88>
ASR.l #5,D0 ;CONVERT LEFT TO LONGS <BAL 15Sep88>
SUB D0,D2 ;CALC LONG COUNT
ADD D0,D0 ;DOUBLE FOR WORDS
ADD D0,D0 ;QUAD FOR BYTES
ADD D0,A1 ;OFFSET DSTPTR
ADD D0,A2 ;OFFSET MASKPTR
;D0 USED BY BIG PATTERN ROUTINES
TST D2 ;SET Z-FLAG BASED ON WORDCOUNT
JMP (A4) ;TAKE MODECASE TO DRAW SLAB
DONESLAB RTS
;---------------------------------------------------------
;
; INTERFACE TO EACH SCAN LINE ROUTINE:
;
; ENTER WITH Z-FLAG SET IF ALL IN ONE LONG
;
; INPUTS: A1: DSTPTR
; A2: MASKPTR
; D1: RIGHTMASK
; D2: LONGCNT
; D3: LEFTMASK
; D4: FGCOLOR
; D5: BKCOLOR
; D6: PATTERN
;
; CLOBBERS: D0,D3,D2,A1,A2
; A3,D6 (BUT NOT IN FASTSLAB)
;
;-------------------------------------------------------
;
; MODE 8 OR 12: PATTERN --> DST
;
; Slab copy using alpha mask <17>
;
; This exact code is in QDciROMPatches.a
slMASK8A
MOVE.L alphaMask(A6),D0 ;get alpha mask
AND.L D0,D1 ;clip left mask with alpha mask
AND.L D0,D3 ;clip right mask with alpha mask
MOVE.L D0,A0 ;save copy of alpha mask
TST D2 ;re-test long count
BRA.S DO8A
END8A AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
NEXT8A MOVE.L D6,D0 ;GET PATTERN DATA
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
AND.L D3,D0 ;MASK PATTERN DATA
NOT.L D3 ;MAKE NOTMASK
AND.L (A1),D3 ;AND NOTMASK WITH OLD DST
OR.L D0,D3 ;FILL HOLE WITH PATTERN
MOVE.L D3,(A1)+ ;UPDATE DST
MOVE.L A0,D3 ;FLUSH MASK to alpha mask
SUB #1,D2 ;DEC LONG COUNT
DO8A BGT NEXT8A ;LOOP FOR ALL LONGS IN ROW
BEQ END8A ;DO LAST LONG WITH MASK
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 8 OR 12: BIG PATTERN --> DST
;
; Slab copy using alpha mask <17>
;
slXMASK8A
MOVE D7,-(SP) ;SAVE WORK REGISTER
MOVE PATHMASK(A6),D7 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D7,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.L PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
MOVE.L alphaMask(A6),D0 ;get alpha mask
AND.L D0,D1 ;clip left mask with alpha mask
AND.L D0,D3 ;clip right mask with alpha mask
MOVE.L D0,A0 ;save copy of alpha mask
TST D2 ;re-test long count
BRA.S XDO8A
XEND8A AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
XNEXT8A MOVE.L 0(A3,D6),D0 ;GET PATTERN DATA
ADDQ #4,D6 ;BUMP PATTERN INDEX
AND D7,D6 ;MASK INDEX INTO PATTERN
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
AND.L D3,D0 ;MASK PATTERN DATA
NOT.L D3 ;MAKE NOTMASK
AND.L (A1),D3 ;AND NOTMASK WITH OLD DST
OR.L D0,D3 ;FILL HOLE WITH PATTERN
MOVE.L D3,(A1)+ ;UPDATE DST
MOVE.L A0,D3 ;FLUSH MASK to alpha mask
SUB #1,D2 ;DEC LONG COUNT
XDO8A BGT XNEXT8A ;LOOP FOR ALL LONGS IN ROW
BEQ XEND8A ;DO LAST LONG WITH MASK
MOVE (SP)+,D7 ;RESTORE WORK REGISTER
RTS
ALIGN Alignment
if 0 then
;-------------------------------------------------------
;
; MODE 8 OR 12: PATTERN --> DST
;
END8 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
NEXT8 MOVE.L D6,D0 ;GET PATTERN DATA
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
AND.L D3,D0 ;MASK PATTERN DATA
NOT.L D3 ;MAKE NOTMASK
AND.L (A1),D3 ;AND NOTMASK WITH OLD DST
OR.L D0,D3 ;FILL HOLE WITH PATTERN
MOVE.L D3,(A1)+ ;UPDATE DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
slMASK8 BGT NEXT8 ;LOOP FOR ALL LONGS IN ROW
BEQ END8 ;DO LAST LONG WITH MASK
RTS
endif
;******************************************************************************************
; QuickerDraw
; Scan line handler for clipped pattern fill copy mode (called by oval, rrect) -- trap $380
; just like whats in QDciPatchROM.a <sm 6/9/92>stb
FillClipScanLine
FCSL1 ; << PB452 BAL>>
FCSL2
slMASK8
AND.L (A2)+,D3 ;use left mask to start with
SUBQ #1,D2
BMI.S DoFCLast0
; special case the left edge
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
MOVE.L (A2)+,D3
SUBQ #1,D2
BMI.S DoFCLast0
; see if we're in the unclipped case; if so, use a faster loop
MOVE.L SEEKMASK(A6),A0 ;get seekRgn address
; CMP.W #$4E75,(A0) ;is it a RTS?
CMP.L #$343C7fff,(A0) ;is it "move.w #$7fff,d2"
BEQ.S DoFCUnclipped ;if so, handle specially
BRA.S FCNotOn1
; here's the loop -- use standard technique of special casing region masks
FCLineLoop
MOVE.L (A2)+,D3 ;fetch region mask
BEQ.S FCOff ;if all zero, can optimize
FCNotOff1
CMP.L MINUSONE,D3 ;all ones? << PB452 BAL>>
BEQ.S FCOn ;if so, optimize
FCNotOn1
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
DBRA D2,FCLineLoop
; handle the last one, using the mask in D1
DoFCLast
MOVE.L (A2)+,D3
DoFCLast0
AND.L D1,D3 ;use right mask
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
RTS
; handle the case of an all zero region mask
FCOff
ADDQ #4,A1 ;skip over it
SUBQ #1,D2
BMI.S DoFCLast
FCOffLoop
MOVE.L (A2)+,D3
BNE.S FCNotOff1
ADDQ #4,A1 ;skip it
DBRA D2,FCOffLoop
BRA.S DoFCLast
; handle the case of an all one's region mask
FCOn
MOVE.L D6,(A1)+
SUBQ #1,D2
BMI.S DoFCLast
FCOnLoop
MOVE.L (A2)+,D3
CMP.L MINUSONE,D3 ; << PB452 BAL>>
BNE.S FCNotOn1
MOVE.L D6,(A1)+
DBRA D2,FCOnLoop
BRA.S DoFCLast
; handle the unclipped case with faster unwound code
DoFCUnclipped
LEA 0(A2,D2.W*4),A2 ;bump region ptr
ADDQ #1,D2 ;compute count to do
CMP.W #8,D2
BLT.S FinishFCUnClip
MOVE.W D2,D0
LSR #3,D0 ;divide by 8
SUBQ #1,D0 ;bias for DBRA
FCUnClipLoop
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
DBRA D0,FCUnClipLoop
; now finish up the last 7 or less
FinishFCUnClip
AND #7,D2
EOR #7,D2
JMP FinishFCUCTab(D2.W*2)
FinishFCUCTab
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
MOVE.L D6,(A1)+
BRA.S DoFCLast
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 9 OR 13: PATTERN OR DST --> DST
;
END9 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
NEXT9 AND.L D6,D3 ;MASK PATTERN DATA
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
MOVE.L D3,D0 ;COPY MASKED, CLIPPED SRC
AND.L D4,D0 ;APPLY FG COLOR TO SRC
NOT.L D3 ;GET NOT MASKED, CLIPPED SRC
AND.L (A1),D3 ;USE TO PUNCH OUT DST
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;MOVE RESULT INTO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
oldslMASK9
BGT NEXT9 ;LOOP FOR ALL LONGS IN ROW
BEQ END9 ;DO LAST LONG WITH MASK
RTS
;******************************************************************************************
; QuickerDraw
; Scan line handler for clipped pattern fill OR mode (called by oval, rrect) -- trap $381
; similar to above, but in OR mode. We can only handle if the foreground pattern
; is all ones; if so, use the copy mode routine to fill.
; just like whats in QDciPatchROM.a <sm 6/9/92>stb
UseOld381
TST.W D2
bra.s oldslMASK9
FillClipOrLine
slMASK9
CMP.L #-1,D6 ;all foreground?
BNE.S UseOld381 ;if not, we can't handle
MOVE.L D4,D6 ;set up fill pattern
BRA slMASK8 ;use common code
;******************************************************************************************
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 10 OR 14: PATTERN XOR DST --> DST
;
END10 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
NEXT10 AND.L D6,D3 ;GET PATTERN DATA
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
EOR.L D3,(A1)+ ;XOR RESULT INTO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
slMASK10
BGT NEXT10 ;LOOP FOR ALL LONGS IN ROW
BEQ END10 ;DO LAST LONG WITH MASK
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 11 OR 15: PATTERN BIC DST --> DST
;
END11 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
NEXT11 AND.L D6,D3 ;MASK PATTERN DATA
AND.L (A2)+,D3 ;GET MASKED, CLIPPED SRC
MOVE.L D3,D0 ;COPY MASKED, CLIPPED SRC
AND.L D5,D0 ;APPLY BK TO SRC
NOT.L D3 ;GET NOT MASKED, CLIPPED SRC
AND.L (A1),D3 ;PUNCH OUT DST DATA
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;PUT RESULT TO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
slMASK11
BGT NEXT11 ;LOOP FOR ALL LONGS IN ROW
BEQ END11 ;DO LAST LONG WITH MASK
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 8 OR 12: BIG PATTERN --> DST
;
slXMASK8big
MOVE D7,-(SP) ;SAVE WORK REGISTER
MOVE PATHMASK(A6),D7 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D7,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
TST D2
BRA.S XDO8
XEND8 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
XNEXT8 MOVE.L 0(A3,D6),D0 ;GET PATTERN DATA
ADDQ #4,D6 ;BUMP PATTERN INDEX
AND D7,D6 ;MASK INDEX INTO PATTERN
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
AND.L D3,D0 ;MASK PATTERN DATA
NOT.L D3 ;MAKE NOTMASK
AND.L (A1),D3 ;AND NOTMASK WITH OLD DST
OR.L D0,D3 ;FILL HOLE WITH PATTERN
MOVE.L D3,(A1)+ ;UPDATE DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
XDO8 BGT XNEXT8 ;LOOP FOR ALL LONGS IN ROW
BEQ XEND8 ;DO LAST LONG WITH MASK
MOVE (SP)+,D7 ;RESTORE WORK REGISTER
RTS
;******************************************************************************************
; QuickerDraw
; Scan line handler for clipped pattern fill copy mode (called by oval, rrect)
; for complex patterns-- trap $384
; this has fixes exactly as shown in QDciPatchROM.a <sm 6/9/92>stb
FillClipXLine
slXMASK8
CMP.W #4,PATHMASK(A6) ;pattern too complex?
BGT.S slXMASK8big ;if so, don't handle
MOVE.L D7,-(SP) ;save work register
; keep the pattern in D6 and D7
ADD.W PATHPOS(A6),D0
AND #4,D0
MOVE.L EXPAT(A6),A0
ADD.l PATVPOS(A6),A0 ; <BAL 07Nov89>
MOVE.L 0(A0,D0),D6 ;get left pattern
EOR.W #4,D0
MOVE.L 0(A0,D0),D7 ;get right pattern
; fetch the leftmost region mask
MOVEQ #-1,D4 ;all ones for comparing
AND.L (A2)+,D3 ;use left mask to start with
SUBQ #1,D2
BMI.S DoFCXLast0
; special case the left edge
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
EXG.L D6,D7
MOVE.L (A2)+,D3
SUBQ #1,D2
BMI.S DoFCXLast0
; see if we're in the unclipped case; if so, use a faster loop
MOVE.L SEEKMASK(A6),A0 ;get seekRgn address
; CMP.W #$4E75,(A0) ;is it a RTS?
CMP.L #$343C7fff,(A0) ;is it "move.w #$7fff,d2"
BEQ.S DoFCXUnclipped ;if so, handle specially
BRA.S FCXNotOn1
; here's the loop -- use standard technique of special casing region masks
FCXLineLoop
MOVE.L (A2)+,D3 ;fetch region mask
BEQ.S FCXOff ;if all zero, can optimize
FCXNotOff1
CMP.L D4,D3 ;all ones?
BEQ.S FCXOn ;if so, optimize
FCXNotOn1
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
EXG.L D6,D7
DBRA D2,FCXLineLoop
; handle the last one, using the mask in D1
DoFCXLast
MOVE.L (A2)+,D3
DoFCXLast0
AND.L D1,D3 ;use right mask
MOVE.L D6,D0 ;get pattern
AND.L D3,D0 ;mask it
NOT.L D3 ;flip mask
AND.L (A1),D3 ;combine with source
OR.L D3,D0 ;form dest longword
MOVE.L D0,(A1)+ ;deposit it
MOVE.L (SP)+,D7 ;restore work reg
RTS
; handle the case of an all zero region mask
FCXOff
ADDQ #4,A1 ;skip over it
EXG.L D6,D7 ;exchange pattern parts even if skipping <SMC 17Oct90> <16>
SUBQ #1,D2
BMI.S DoFCXLast
FCXOffLoop
MOVE.L (A2)+,D3
BNE.S FCXNotOff1
ADDQ #4,A1 ;skip it
EXG.L D6,D7 ;exchange pattern parts even if skipping <SMC 17Oct90> <16>
DBRA D2,FCXOffLoop
BRA.S DoFCXLast
; handle the case of an all one's region mask
FCXOn
MOVE.L D6,(A1)+
EXG.L D6,D7
SUBQ #1,D2
BMI.S DoFCXLast
FCXOnLoop
MOVE.L (A2)+,D3
CMP.L D4,D3
BNE.S FCXNotOn1
MOVE.L D6,(A1)+
EXG.L D6,D7
DBRA D2,FCXOnLoop
BRA.S DoFCXLast
; handle the unclipped case with faster unwound code
DoFCXUnclipped
LEA 0(A2,D2.W*4),A2 ;bump region ptr
ADDQ #1,D2 ;compute count to do
CMP.W #8,D2
BLT.S FinishFCXUnClip
MOVE.W D2,D0
LSR #3,D0 ;divide by 8
SUBQ #1,D0 ;bias for DBRA
FCXUnClipLoop
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
DBRA D0,FCXUnClipLoop
; now finish up the last 7 or less
FinishFCXUnClip
AND #7,D2
EOR #7,D2
BTST #0,D2
BEQ.S @0
EXG.L D6,D7
@0
JMP FinishFCXUCTab(D2.W*2)
FinishFCXUCTab
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
MOVE.L D7,(A1)+
MOVE.L D6,(A1)+
EXG.L D6,D7
BRA DoFCXLast
;******************************************************************************************
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 9 OR 13: BIG PATTERN OR DST --> DST
;
slXMASK9
MOVE D7,-(SP) ;SAVE WORK REGISTER
MOVE PATHMASK(A6),D7 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D7,D6 ;MASK INTEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S XDO9 ;AND JUMP INTO LOOP
XEND9 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
XNEXT9 AND.L 0(A3,D6),D3 ;MASK PATTERN DATA
ADDQ #4,D6 ;BUMP INDEX INTO PATTERN
AND D7,D6 ;MASK INDEX INTO PATTERN
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
MOVE.L D3,D0 ;COPY MASKED, CLIPPED SRC
AND.L D4,D0 ;APPLY FG COLOR TO SRC
NOT.L D3 ;GET NOT MASKED, CLIPPED SRC
AND.L (A1),D3 ;USE TO PUNCH OUT DST
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;MOVE RESULT INTO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
XDO9 BGT XNEXT9 ;LOOP FOR ALL LONGS IN ROW
BEQ XEND9 ;DO LAST LONG WITH MASK
MOVE (SP)+,D7 ;RESTORE WORK REGISTER
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 10 OR 14: BIG PATTERN XOR DST --> DST
;
slXMASK10
MOVE D7,-(SP) ;SAVE WORK REGISTER
MOVE PATHMASK(A6),D7 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D7,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S XDO10 ;AND JUMP INTO LOOP
XEND10 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
XNEXT10 AND.L 0(A3,D6),D3 ;MASK PATTERN DATA
ADDQ #4,D6 ;BUMP INDEX INTO PATTERN
AND D7,D6 ;MASK INDEX INTO PATTERN
AND.L (A2)+,D3 ;MERGE MASK AND CLIPRGN MASK
EOR.L D3,(A1)+ ;XOR RESULT INTO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
XDO10 BGT XNEXT10 ;LOOP FOR ALL LONGS IN ROW
BEQ XEND10 ;DO LAST LONG WITH MASK
MOVE (SP)+,D7 ;RESTORE WORK REGISTER
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 11 OR 15: BIG PATTERN BIC DST --> DST
;
slXMASK11
MOVE D7,-(SP) ;SAVE WORK REGISTER
MOVE PATHMASK(A6),D7 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D7,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S XDO11 ;AND JUMP INTO LOOP
XEND11 AND.L D1,D3 ;COMBINE RIGHT AND LEFT MASK
XNEXT11 AND.L 0(A3,D6),D3 ;MASK PATTERN DATA
ADDQ #4,D6 ;BUMP INDEX INTO PATTERN
AND D7,D6 ;MASK INDEX INTO PATTERN
AND.L (A2)+,D3 ;GET MASKED, CLIPPED SRC
MOVE.L D3,D0 ;COPY MASKED, CLIPPED SRC
AND.L D5,D0 ;APPLY BK TO SRC
NOT.L D3 ;GET NOT MASKED, CLIPPED SRC
AND.L (A1),D3 ;PUNCH OUT DST DATA
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;PUT RESULT TO DST
MOVEQ #-1,D3 ;FLUSH MASK
SUB #1,D2 ;DEC LONG COUNT
XDO11 BGT XNEXT11 ;LOOP FOR ALL LONGS IN ROW
BEQ XEND11 ;DO LAST LONG WITH MASK
MOVE (SP)+,D7 ;RESTORE WORK REGISTER
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 42: PAT + DST --> DST (no pin)
; D4 is destination offset rather than foreground color
; D5 is inverse table size rather than background color
slAddOver
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR.S arithSetup ;set up registers for slab bit blt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A4)+,D0 ;red get source color value
ADD (A5)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;green get source color value
ADD (A5)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;blue get source color value
ADD (A5)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;——————————————————————————————————————————————————————
; Utility arithSetup
; sets up registers for arithmetic modes:
;
; A0 = base offset in bits (left * pixelSize)
;
; D4 = 0 (destination bit offset) D5 = inverse color table resolution
; D6 = source bit offset D7 = bits per pixel
; A0 = color table pointer A3 = source pointer
;
arithSetup
MOVEQ #0,D4 ;start off dest. at 0
MOVE invSize(A6),D5 ;set up resolution of inverse color table
MOVEQ #0,D6 ;start with left side of pattern
MOVEQ #0,D7 ;zero high word
MOVE dstPix+pixelSize(A6),D7 ;set up pixel size
MOVE.L A0,A3 ;set up pointer to pat long in case pattern is small
CMP #4,patRow(A6) ;big pat?
BLE.S @skipBig
move.l slabLeft(a6),d6 ;get bit offset into src <BAL 17Jan89>
and.l #~$1f,d6 ;truncate to long boundary <BAL 18Jan89>
move.w patHPos(a6),a0 ;make into a long <BAL 17Jan89>
add.l a0,D6 ;compute src offset in d6 <BAL 17Jan89>
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
@skipBig
SUB.L D7,D6 ;less 1 since bumped before used
MOVE.L colorTable(A6),A0 ;set up pointer to color table
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 41: PAT + DST --> DST (pin to max)
; D4 is destination offset rather than foreground color
; D5 is inverse table size rather than background color
slAddPin
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR.S arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A4)+,D0 ;red get source color value
ADD (A5)+,D0 ; combine source and destination
BCS.S @tooBigRed
CMP pin+4(A6),D0 ;bigger than pin value?
BLS.S @notTooBigRed ;no, no problem
@tooBigRed
MOVE pin+4(A6),D0
@notTooBigRed
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;green get source color value
ADD (A5)+,D0 ; combine source and destination
BCS.S @tooBigGreen
CMP pin+2(A6),D0 ;bigger than pin value?
BLS.S @notTooBigGreen ;no, no problem
@tooBigGreen
MOVE pin+2(A6),D0
@notTooBigGreen
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;blue get source color value
ADD (A5)+,D0 ; combine source and destination
BCS.S @tooBigBlue
CMP pin(A6),D0 ;bigger than pin value?
BLS.S @notTooBigBlue ;no, no problem
@tooBigBlue
MOVE pin(A6),D0
@notTooBigBlue
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 46: DST - PAT --> DST (no pin)
; D4 is destination offset rather than foreground color
; D5 is inverse table size rather than background color
slSubOver
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A5)+,D0 ;red get source color value
SUB (A4)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A5)+,D0 ;green get source color value
SUB (A4)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A5)+,D0 ;blue get source color value
SUB (A4)+,D0 ; combine source and destination
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 43: DST - PAT --> DST (pin to min)
; D4 is destination offset rather than foreground color
; D5 is inverse table size rather than background color
slSubPin
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A5)+,D0 ;red get destination color value
SUB (A4)+,D0 ; less source color
BCS.S @tooBigRed
CMP pin+4(A6),D0 ;bigger than pin value?
BHS.S @notTooBigRed ;no, no problem
@tooBigRed
MOVE pin+4(A6),D0
@notTooBigRed
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A5)+,D0 ;green get destination color value
SUB (A4)+,D0 ; less source color
BCS.S @tooBigGreen
CMP pin+2(A6),D0 ;bigger than pin value?
BHS.S @notTooBigGreen ;no, no problem
@tooBigGreen
MOVE pin+2(A6),D0
@notTooBigGreen
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A5)+,D0 ;blue get destination color value
SUB (A4)+,D0 ; less source color
BCS.S @tooBigBlue
CMP pin(A6),D0 ;bigger than pin value?
BHS.S @notTooBigBlue ;no, no problem
@tooBigBlue
MOVE pin(A6),D0
@notTooBigBlue
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 45: MAX(PAT, DST) --> DST
;
slMax
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A4)+,D0 ;Red get pattern color value
CMP (A5),D0 ; compare with destination color
BHS.S @gotTheMaxRed ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMaxRed
ADDQ #2,A5 ; advance to next color
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;Blue get pattern color value
CMP (A5),D0 ; compare with destination color
BHS.S @gotTheMaxBlue ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMaxBlue
ADDQ #2,A5 ; advance to next color
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;Green get pattern color value
CMP (A5),D0 ; compare with destination color
BHS.S @gotTheMaxGreen ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMaxGreen
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 47: MIN(PAT, DST) --> DST
;
slMin
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A4)+,D0 ;Red get pattern color value
CMP (A5),D0 ; compare with destination color
BLS.S @gotTheMinRed ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMinRed
ADDQ #2,A5 ; advance to next color
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;Blue get pattern color value
CMP (A5),D0 ; compare with destination color
BLS.S @gotTheMinBlue ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMinBlue
ADDQ #2,A5 ; advance to next color
ASL.L D5,D0 ; save the top bits in the top word
MOVE (A4)+,D0 ;Green get pattern color value
CMP (A5),D0 ; compare with destination color
BLS.S @gotTheMinGreen ; if pattern is larger, use pattern
MOVE (A5),D0 ; if destination is larger, use destination
@gotTheMinGreen
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ;r, g, b in high word
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 40: AVG(SRC, DST, WEIGHT) --> DST
slAvg
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
MOVE.L D1,-(SP) ;free up register
BSR arithSetup ;set up registers for slab bitblt
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA @loopEnd
@loopRight
AND.L (SP)+,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
LEA red(A0,D0*8),A4 ;figure out where it lives in the color table
BFEXTU (A1){D4:D7},D0 ;a pixel of the destination
LEA red(A0,D0*8),A5 ;figure out where destination lives
MOVE (A4)+,D0 ;red get source color value
MULU weight+4(A6),D0 ; weight varies from 0 to 1
MOVE (A5)+,D1 ; get destination
MULU notWeight+4(A6),D1 ; weight varies from 1 to 0
ADD.L D1,D0 ; combine them
CLR D0 ; clear low word
SWAP D0 ; high word is interesting part
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ; and toss remaining bits
ASL D5,D0 ; move to the green position
ASL D5,D0 ; move to the red position
MOVE D0,-(SP) ; save it
MOVE (A4)+,D0 ;green get source color value
MULU weight+2(A6),D0 ; weight varies from 0 to 1
MOVE (A5)+,D1 ; get destination
MULU notWeight+2(A6),D1 ; weight varies from 1 to 0
ADD.L D1,D0 ; combine them
CLR D0 ; clear low word
SWAP D0 ; high word is interesting part
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ; and toss remaining bits
ASL D5,D0 ; move to the green position
OR D0,(SP) ;combine with the red bits
MOVE (A4)+,D0 ;blue get source color value
MULU weight(A6),D0 ; weight varies from 0 to 1
MOVE (A5)+,D1 ; get destination
MULU notWeight(A6),D1 ; weight varies from 1 to 0
ADD.L D1,D0 ; combine them
CLR D0 ; clear low word
SWAP D0 ; high word is interesting part
ASL.L D5,D0 ; save the top bits in the top word
SWAP D0 ; and toss remaining bits
OR (SP)+,D0 ;add in the red and green
MOVE.B ([invColor,A6],D0,itTable),D0 ;get the pixel value of the additive sum
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 58: (pat as mask) background color <--> hilite color
;
;
; Note that a fast case could be implemented (like in rgnblt, bitblt) if the pattern source
; was known to be black.
;
; Contains the fix from QDciPatchROM.a
slHilite
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
BFEXTU transColor(A6){0:D7},D5 ;get a pixel of the background color
BFEXTU hilitColor(A6){0:D7},D0 ;get a pixel of the hilite color
MOVE.L D0,A0 ;save the hilite color pixel in a free register
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
CMP.L D5,D0 ; <•••>
BEQ.S @skip
BFEXTU (A1){D4:D7},D0 ;get a pixel of the destination
CMP.L D5,D0 ;same as the background color?
BNE.S @tryNew
MOVE.L A0,D0 ;put hilite color in data register
BFINS D0,(A1){D4:D7} ;move hilite color to destination
BRA.S @skip
@tryNew
CMP.L A0,D0 ;same as new color?
BNE.S @skip
BFINS D5,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 44: PAT less bg --> DST
; Note that unlike the BitBlt and RgnBlt cases, this has no optimization for when a
; long of the pattern equals the background. The optimizations in BitBlt and RgnBlt
; are intended to allow sources other than patterns to be quickly masked and blitted.
slTransparent
MOVEM.L D7/A4-A5,-(SP) ;preserve extra registers
BSR arithSetup ;set up registers for slab bitblt
BFEXTU transColor(A6){0:D7},D5 ;get a pixel of the transparent color
TST D2 ;TEST NUMBER OF BYTES TO DO
BRA.S @loopEnd
@loopRight
AND.L D1,D3 ;combine left and right masks
@loopTop
ADD.L D7,D6 ;advance the pattern
AND patHMask(A6),D6 ;constrict it to the width of the pattern
BFEXTU D3{D4:D7},D0 ;a pixel of the mask
BEQ.S @skip
BFEXTU (A2){D4:D7},D0 ;a pixel of the clip region
BEQ.S @skip
BFEXTU (A3){D6:D7},D0 ;get a pixel of the pattern
CMP.l D5,D0 ;same as the background? <BAL 17Jan89>
BEQ.S @skip
BFINS D0,(A1){D4:D7} ;move to the destination
@skip
ADD.L D7,D4 ;bump destination and mask
MOVE D4,D0 ;copy destination offset
AND #31,D0 ;combine with long sized mask
BNE.S @loopTop ;loop if havent finished a long yet
MOVEQ #-1,D3 ;flush the mask
SUBQ #1,D2 ;decrement long counter
@loopEnd
BGT.S @loopTop ;do it for all of the pixels on the line (or within the mask)
BEQ.S @loopRight
MOVEM.L (SP)+,D7/A4-A5 ;restore regs
RTS
ALIGN Alignment
;--------------------------------------------------------------------------
;
;
; Here begins the arithmetic transfer loops for 32 bits/pixel:
;
;
;
;--------------------------------------------------------------------------
;
; MODE 42: PAT + DST --> DST (no pin)
;-------------------------------------------------------
; a0 = hi bit mask d0 = hi bit clring mask
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = src msb's
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = dst msb's
;-------------------------------------------------------
slAddOver32
move.l d7,-(sp) ;preserve d7
BSR arithSetup32 ;set up registers for slab bitblt
move.l #~$ff808080,d0 ;get high bit clearing mask
move.l #$00808080,a0 ;get high bit mask
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d1 ;get src pixel
move.l a0,d7 ;copy high bit mask
and.l d1,d7 ;remember src msb's
and.l d0,d1 ;mask out stragglers
move.l (a1),d5 ;get dest pixel
move.l a0,d3 ;copy high bit mask
and.l d5,d3 ;remember dst msb's
and.l d0,d5 ;mask out stragglers
add.l d1,d5 ;merge src with dst
eor.l d7,d3 ;compute partial sum of msb's
eor.l d3,d5 ;compute partial sum of msb's
MOVE.L d5,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;——————————————————————————————————————————————————————
; Utility arithSetup
; sets up registers for 32 bit arithmetic modes:
;
;
; INPUTS: A1: DSTPTR
; A2: MASKPTR
; D1: RIGHTMASK
; D2: LONGCNT
; D3: LEFTMASK
; D4: FGCOLOR
; D5: BKCOLOR
; D6: PATTERN
;
; CLOBBERS: D0,D3,D2,A1,A2
; A3,D6 (BUT NOT IN FASTSLAB)
arithSetup32
subq #1,d2 ;make zero based
MOVE PATHMASK(A6),D4 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D4,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 41: PAT + DST --> DST (pin to max)
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = lo3Bytes mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = pin pixel 0rgb
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slAddPin32
move.l d7,a0 ;save d7 in a0
BSR arithSetup32 ;set up registers for slab bitblt
;set up pin pixel as 0rgb in D3
moveq #0,d3 ;start fresh, waste iTabRes
move.b pin+4(a6),d3 ;pick up red
swap d3 ;put in byte 3
move.w pin+2(a6),d3 ;get green in byte 2
move.b pin(a6),d3 ;put blue in lo byte
move.l Lo3Bytes,d1 ;pick up mask
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d7 ;get src pixel
and.l d1,d7 ;waste high byte
move.l d7,d0 ;make a copy of the src xrgb
move.l (a1),d5 ;get dest pixel
and.l d1,d5 ;waste high byte
clr.b d0 ;prevent carries from below
add.w d5,d0 ;add green components
BCS.S @PinGreen
cmp.w d3,d0 ;do we need to pin result?
bls.s @GreenOK
@PinGreen
move.w d3,d0 ;use pin value instead
@GreenOK
move.b d7,d0 ;get src blue
add.b d5,d0 ;add dest blue
BCS.S @PinBlue
cmp.b d3,d0 ;do we need to pin result?
bls.s @BlueOK
@PinBlue
move.b d3,d0 ;use pin value instead
@BlueOK
clr.w d5 ;now d5 has only red in byte 3
add.l d5,d0 ;add red components
cmp.l d3,d0 ;compare red components
bls.s @RedOK
@PinRed
swap d3 ;get max red in lo word
swap d0 ;get too big red in lo word
move.w d3,d0 ;pin to max red
swap d0 ;get back 0rgb
swap d3 ;restore pin pixel
@RedOK
MOVE.L d0,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l a0,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 46: DST - PAT --> DST (no pin)
;
;-------------------------------------------------------
; a0 = d0 = hi bit clring mask
; a1 = dstPtr d1 = high bit mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = src msb's
; a4 = d4 = dst msb's
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slSubOver32
move.l d7,a0 ;save d7 in a0
BSR arithSetup32 ;set up registers for slab bitblt
move.l #~$ff808080,d0 ;get high bit clearing mask
move.l #$00808080,d1 ;get high bit mask
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d7 ;get src pixel
move.l d1,d3 ;copy high bit mask
and.l d7,d3 ;remember src msb's
eor.l d1,d3 ;invert src msb's
and.l d0,d7 ;mask out stragglers
move.l (a1),d5 ;get dest pixel
move.l d1,d4 ;copy high bit mask
and.l d5,d4 ;remember dst msb's
and.l d0,d5 ;mask out high byte
or.l d1,d5 ;force high bits on
sub.l d7,d5 ;compute dst - src
eor.l d3,d4 ;compute partial sum of msb's
eor.l d4,d5 ;compute partial sum of msb's
MOVE.L d5,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w patHMask(a6),d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l a0,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 43: DST - PAT --> DST (pin to min)
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = lo3Bytes mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = pin pixel 0rgb
; a4 = d4 = patHMask
; a5 = d5 = src pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = dst pixel
;-------------------------------------------------------
slSubPin32
move.l d7,a0 ;save d7 in a0
BSR arithSetup32 ;set up registers for slab bitblt
;set up pin pixel as 0rgb in D3
moveq #0,d3 ;start fresh, waste iTabRes
move.b pin+4(a6),d3 ;pick up red
swap d3 ;put in byte 3
move.w pin+2(a6),d3 ;get green in byte 2
move.b pin(a6),d3 ;put blue in lo byte
move.l Lo3Bytes,d1 ;pick up mask
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d5 ;get src pixel
and.l d1,d5 ;waste high byte
move.l (a1),d7 ;get dest pixel
and.l d1,d7 ;waste high byte
move.l d7,d0 ;make a copy of the dst xrgb
st d0 ;prevent borrows from below
sub.w d5,d0 ;sub green components
BCS.S @PinGreen
cmp.w d3,d0 ;do we need to pin result?
bhs.s @GreenOK
@PinGreen
move.w d3,d0 ;use pin value instead
@GreenOK
move.b d7,d0 ;get dest blue
sub.b d5,d0 ;sub src blue
BCS.S @PinBlue
cmp.b d3,d0 ;do we need to pin result?
bhs.s @BlueOK
@PinBlue
move.b d3,d0 ;use pin value instead
@BlueOK
clr.w d5 ;now d5 has only red in byte 3
sub.l d5,d0 ;sub red components
cmp.l d3,d0 ;compare red components
bge.s @RedOK
@PinRed
swap d3 ;get max red in lo word
swap d0 ;get too big red in lo word
move.w d3,d0 ;pin to max red
swap d0 ;get back 0rgb
swap d3 ;restore pin pixel
@RedOK
MOVE.L d0,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l a0,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 45: MAX(PAT, DST) --> DST
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slMax32
BSR arithSetup32 ;set up registers for slab bitblt
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d1 ;get src pixel
move.l (a1),d5 ;get dest pixel
move.l d5,d0 ;make a copy of the dest xrgb
cmp.w d1,d0 ;compare g,b components
BHI.S @gotMaxGreen
move.w d1,d0 ;keep the bigger of the two
move.b d5,d0 ;prime for blue
@gotMaxGreen
cmp.b d1,d5 ;compare blue components
BHI.S @gotMaxBlue
move.b d1,d0 ;keep the bigger of the two
@gotMaxBlue
swap d1
swap d0
cmp.b d1,d0 ;compare red components
BHI.S @gotMaxRed
move.b d1,d0 ;keep the bigger of the two
@gotMaxRed
swap d0 ;get new xrgb
MOVE.L d0,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 47: MIN(PAT, DST) --> DST
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slMin32
BSR arithSetup32 ;set up registers for slab bitblt
@blit tst.l (a2)+ ;a pixel of the clip region
beq.s @skip
move.l 0(a3,d6),d1 ;get src pixel
move.l (a1),d5 ;get dest pixel
move.l d5,d0 ;make a copy of the dest xrgb
cmp.w d1,d0 ;compare g,b components
BLS.S @gotMinGreen
move.w d1,d0 ;keep the smaller of the two
move.b d5,d0 ;prime for blue
@gotMinGreen
cmp.b d1,d5 ;compare blue components
BLS.S @gotMinBlue
move.b d1,d0 ;keep the smaller of the two
@gotMinBlue
swap d1
swap d0
cmp.b d1,d0 ;compare red components
BLS.S @gotMinRed
move.b d1,d0 ;keep the smaller of the two
@gotMinRed
swap d0 ;get new xrgb
MOVE.L d0,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 40: AVG(SRC, DST, WEIGHT) --> DST
;
; CLOBBERS: D0,D3,D2,A1,A2
; A3,D6 (BUT NOT IN FASTSLAB)
;-------------------------------------------------------
; a0 = /last dst d0 = red weight
; a1 = dstPtr d1 = blue/grn weight (scanCount)
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = /last src
; a4 = d4 = /last result
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slAvg32
lea @slAvg32Slow,a4 ;assume, general blend32 from now on
lea weight(a6),a0 ;point to weights
move.w (a0)+,d3
cmp.w (a0)+,d3 ;is opColor gray?
bne.s @slAvg32Slow
cmp.w (a0),d3
bne.s @slAvg32Slow
addq #1,d3 ;yes, check for gray values of $8000 or $7fff
and.w #$fffe,d3
cmp.w #$8000,d3
bne.s @slAvg32Slow
lea @slAvg32Half,a4 ;use fast 50% blend32 from now on
bra @slAvg32Half
ALIGN Alignment
;-------------------------------------------------------
;
; General blend case for non 50% gray weights
;
;
@slAvg32Slow
MOVE.L D7,-(SP) ;preserve extra registers
BSR arithSetup32 ;set up registers for slab bitblt
lea weight(a6),a0 ;point at blue weight
move.l (a0)+,d1 ;get blue/green weight
move.w (a0),d0 ;get red weight
@short0 moveq #0,d4 ;init last result
move.l d4,d3 ;init last src
move.l d4,a0 ;init last dst
@blit tst.l (A2)+ ;a pixel of the clip region
BEQ.S @skip
move.l 0(a3,d6),d7 ;get src pixel
move.l (a1),d5 ;get dest pixel
@short1 cmp.l d3,d7 ;same as last time?
bne.s @blue ;no, go do it
cmp.l a0,d5 ;same as last time?
beq.s @again ;yes, go fast
@blue moveq #0,d3 ;clr out high end
move.b d7,d3 ;get src blue
swap d1 ;get blue weight
mulu.w d1,d3 ;% blue
moveq #0,d4 ;clr out high end
move.b d5,d4 ;get dst blue
neg.w d1
mulu.w d1,d4 ;% blue
neg.w d1
add.l d3,d4 ;get 24 bits of dst blue
swap d4 ;dst blue
move.w d4,a0 ;a0 has 000B
@grn move.w d7,d3 ;get src grn
lsr.w #8,d3
swap d1 ;get grn weight
mulu.w d1,d3 ;% grn
move.w d5,d4 ;get dst grn
lsr.w #8,d4
neg.w d1
mulu.w d1,d4 ;% grn
neg.w d1
add.l d3,d4 ;get 24 bits of dst grn
swap d4 ;dst grn
lsl.w #8,d4
add.w d4,a0 ;a0 has 00GB
@red moveq #0,d3 ;clr out high end
swap d7
move.b d7,d3 ;get src red
mulu.w d0,d3 ;% red
moveq #0,d4 ;clr out high end
swap d5
move.b d5,d4 ;get dst red
neg.w d0
mulu.w d0,d4 ;% red
neg.w d0
add.l d3,d4 ;get 24 bits of dst red
move.w a0,d4 ;d4 has 0RGB
@short2 swap d5 ;get back dst
move.l d5,a0 ;save for short circuit
swap d7 ;get back src
move.l d7,d3 ;save for short circuit
@again MOVE.L d4,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w patHMask(a6),d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
MOVE.L (SP)+,D7 ;restore regs
RTS
ALIGN Alignment
;--------------------------------------------
;
; Optimized 50% blend case for 32 bits/pixel
;
;-------------------------------------------------------
; a0 = low bit mask d0 = high bit mask
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = lsb's of result
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
@slAvg32Half
BSR arithSetup32 ;set up registers for slab bitblt
move.l #~$ff808080,d0 ;get high bit mask
move.l #$10101,a0 ;get low bit mask
@blit2 tst.l (A2)+ ;a pixel of the clip region
BEQ.S @skip2
move.l 0(a3,d6),d1 ;get src pixel
move.l a0,d3 ;copy low bit mask
and.l d1,d3 ;remember src lsb's
lsr.l #1,d1 ;get almost 1/2 of it
and.l d0,d1 ;mask out stragglers
move.l (a1),d5 ;get dest pixel
and.l d5,d3 ;compute carry out of lsb
lsr.l #1,d5 ;get almost 1/2 of it
and.l d0,d5 ;mask out stragglers
add.l d5,d1 ;merge src with dst
add.l d3,d1 ;propagate carrys
MOVE.L d1,(a1) ;write pattern to dest
@skip2 addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit2 ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;--------------------------------------------
;
; Mode: 36 Transparent for 32 bits/pixel
;
;-------------------------------------------------------
; a0 = d0 =
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = backColor
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slTransparent32
BSR arithSetup32 ;set up registers for slab bitblt
move.l transColor(A6),D5 ;get a pixel of the transparent color
@blit tst.l (A2)+ ;a pixel of the clip region
BEQ.S @skip
move.l 0(a3,d6),d1 ;get src pixel
cmp.l d1,d5 ;is src backColor?
beq.s @skip ;yes, don't write to dst
MOVE.L d1,(a1) ;write pattern to dest
@skip addq.l #4,a1 ;bump dst ptr
addq.l #4,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;--------------------------------------------------------------------------
;
;
; Here begin the arithmetic transfer loops for 16 bits/pixel:
;
;
;
;--------------------------------------------------------------------------
;
; MODE 42: PAT + DST --> DST (no pin)
;-------------------------------------------------------
; a0 = hi bit mask d0 = hi bit clring mask
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = src msb's
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = dst msb's
;-------------------------------------------------------
slAddOver16
move.l d7,-(sp) ;preserve d7
BSR.s arithSetup16 ;set up registers for slab bitblt
move.w #$3def,d0 ;get high bit clearing mask
move.w #$4210,a0 ;get high bit mask
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
move.w 0(a3,d6),d1 ;get src pixel
move.w a0,d7 ;copy high bit mask
and.w d1,d7 ;remember src msb's
and.w d0,d1 ;mask out stragglers
move.w (a1),d5 ;get dest pixel
move.w a0,d3 ;copy high bit mask
and.w d5,d3 ;remember dst msb's
and.w d0,d5 ;mask out stragglers
add.w d1,d5 ;merge src with dst
eor.w d7,d3 ;compute partial sum of msb's
eor.w d3,d5 ;compute partial sum of msb's
MOVE.w d5,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;——————————————————————————————————————————————————————
; Utility arithSetup
; sets up registers for 16 bit arithmetic modes:
;
; INPUT
; REGISTERS: A0: D0: CLOBBERED ;
; A1: DSTPTR D1: CLOBBERED ;
; A2: MASKPTR D2: LONGCNT ;
; A3: SRCPTR D3: FGCOLOR ;
; A4: modecase D4: BKCOLOR ;
; A5: D5: CLOBBERED ;
; A6: D6: DSTALIGN ;
; A7: D7: PixelSize ;
; ;
arithSetup16
asl.w #1,d2 ;2 pixels per long
beq.s @oneLong
subq #1,d2 ;make zero based
neg d1 ;convert mask to extra pixel cnt
add d1,d2 ;include right pixel of last long
swap d1
neg d1 ;convert mask to extra pixel cnt
add d1,d2 ;include right pixel of last long
@noRight
tst.l d3 ;worry about first pixel?
bmi.s @noLeft ;yes, do it!
subq #1,d2 ;shorten count
@skipLeft
addq #2,a2 ;bump mask past first pixel
addq #2,a3 ;bump src past first pixel
addq #2,a1 ;bump dst past first pixel
addq #2,d0 ;bump pat index*
@noLeft
MOVE PATHMASK(A6),D4 ;GET HORIZ MASK
MOVE D0,D6 ;GET LEFT AS INDEX INTO PATTERN
ADD PATHPOS(A6),D6 ;GET OFFSET FROM PATTERN BASE
AND D4,D6 ;MASK INDEX INTO PATTERN
MOVE.L EXPAT(A6),A3 ;GET PATTERN POINTER
ADD.l PATVPOS(A6),A3 ;ADD VERT OFFSET INTO PATTERN <BAL 22Jan89>
RTS
@oneLong
and.l d1,d3 ;combine left and right mask
bpl.s @skipLeft ;skip first pixel
neg.w d3 ;turn right pixel in to bump
add.w d3,d2 ;conditionally bump count
bra.s @noLeft
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 41: PAT + DST --> DST (pin to max)
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = lo3Bytes mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = pin pixel 0rgb
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slAddPin16
move.l d7,-(sp) ;preserve d7
BSR.s arithSetup16 ;set up registers for slab bitblt
;set up pin pixel as 0rgb in D3
moveq #0,d3 ;start fresh, waste iTabRes
move.b pin+4(a6),d3 ;pick up red
lsr.b #3,d3 ;get right aligned 5 bits
swap d3 ;put in byte 3
move.w pin+2(a6),d3 ;get green in byte 2
lsr.w #3,d3 ;get right aligned 5 bits
move.b pin(a6),d3 ;put blue in lo byte
lsr.b #3,d3 ;right flush blue
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
moveq #0,d7
move.w 0(a3,d6),d7 ;get src pixel
add.w d7,d7 ;waste high bit
lsl.l #5,d7 ;but red in byte 3
lsr.w #3,d7 ;but green in byte 2, blue in lo byte
lsr.b #3,d7 ;right flush blue
moveq #0,d5
move.w (a1),d5 ;get dest pixel
add.w d5,d5 ;waste high bit
lsl.l #5,d5 ;but red in byte 3
lsr.w #3,d5 ;but green in byte 2, blue in lo byte
lsr.b #3,d5 ;right flush blue
add.l d5,d7 ;add all components at once
move.l d7,d0 ;prime result with red
cmp.l d3,d0 ;do we need to pin result?
bls.s @redOK ;no, don't pin
move.l d3,d0 ;use pin value instead
@redOK
move.w d7,d0 ;prime result with green
cmp.w d3,d0 ;do we need to pin result?
bls.s @greenOK ;no, don't pin
move.w d3,d0 ;use pin value instead
@greenOK
move.b d7,d0 ;prime result with blue
cmp.b d3,d0 ;do we need to pin result?
bls.s @blueOK ;no, don't pin
move.b d3,d0 ;use pin value instead
@blueOK
lsl.b #3,d0 ;rejoin green/blue
lsl.w #3,d0 ;rejoin red/green/blue
lsr.l #6,d0 ;right flush red/green/blue
MOVE.w d0,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 46: DST - PAT --> DST (no pin)
;
;-------------------------------------------------------
; a0 = d0 = hi bit clring mask
; a1 = dstPtr d1 = high bit mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = src msb's
; a4 = d4 = dst msb's
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slSubOver16
move.l d7,-(sp) ;preserve d7
BSR arithSetup16 ;set up registers for slab bitblt
move.w #$3def,d0 ;get high bit clearing mask
move.w #$4210,d1 ;get high bit mask
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
move.w 0(a3,d6),d7 ;get src pixel
move.w d1,d3 ;copy high bit mask
and.w d7,d3 ;remember src msb's
eor.w d1,d3 ;invert src msb's
and.w d0,d7 ;mask out stragglers
move.w (a1),d5 ;get dest pixel
move.w d1,d4 ;copy high bit mask
and.w d5,d4 ;remember dst msb's
and.w d0,d5 ;mask out high byte
or.w d1,d5 ;force high bits on
sub.w d7,d5 ;compute dst - src
eor.w d3,d4 ;compute partial sum of msb's
eor.w d4,d5 ;compute partial sum of msb's
MOVE.w d5,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w patHMask(a6),d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 43: DST - PAT --> DST (pin to min)
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = lo3Bytes mask
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = pin pixel 0rgb
; a4 = d4 = patHMask
; a5 = d5 = src pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = dst pixel
;-------------------------------------------------------
slSubPin16
move.l d7,-(sp) ;preserve d7
BSR arithSetup16 ;set up registers for slab bitblt
;set up pin pixel as 0rgb in D3
moveq #0,d3 ;start fresh, waste iTabRes
move.b pin+4(a6),d3 ;pick up red
lsr.b #3,d3 ;get right aligned 5 bits
swap d3 ;put in byte 3
move.w pin+2(a6),d3 ;get green in byte 2
lsr.w #3,d3 ;get right aligned 5 bits
move.b pin(a6),d3 ;put blue in lo byte
lsr.b #3,d3 ;right flush blue
move.l #$808080,d1 ;borrow stopper
add.l d1,d3 ;prevent borrows from crossing byte boundaries
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
moveq #0,d7
move.w 0(a3,d6),d7 ;get src pixel
add.w d7,d7 ;waste high bit
lsl.l #5,d7 ;but red in byte 3
lsr.w #3,d7 ;but green in byte 2, blue in lo byte
lsr.b #3,d7 ;right flush blue
moveq #0,d5
move.w (a1),d5 ;get dest pixel
add.w d5,d5 ;waste high bit
lsl.l #5,d5 ;but red in byte 3
lsr.w #3,d5 ;but green in byte 2, blue in lo byte
lsr.b #3,d5 ;right flush blue
add.l d1,d5 ;prevent borrows from crossing byte boundaries
sub.l d7,d5 ;sub all components at once
move.l d5,d0 ;prime result with red
cmp.l d3,d0 ;do we need to pin result?
bhs.s @redOK ;no, don't pin
move.l d3,d0 ;use pin value instead
@redOK
move.w d5,d0 ;prime result with green
cmp.w d3,d0 ;do we need to pin result?
bhs.s @greenOK ;no, don't pin
move.w d3,d0 ;use pin value instead
@greenOK
move.b d5,d0 ;prime result with blue
cmp.b d3,d0 ;do we need to pin result?
bhs.s @blueOK ;no, don't pin
move.b d3,d0 ;use pin value instead
@blueOK
lsl.b #3,d0 ;rejoin green/blue
lsl.w #3,d0 ;rejoin red/green/blue
lsr.l #6,d0 ;right flush red/green/blue
MOVE.w d0,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 45: MAX(PAT, DST) --> DST
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slMax16
move.l d7,-(sp) ;preserve d7
BSR arithSetup16 ;set up registers for slab bitblt
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
moveq #0,d7
move.w 0(a3,d6),d7 ;get src pixel
add.w d7,d7 ;waste high bit
lsl.l #5,d7 ;but red in byte 3
lsr.w #3,d7 ;but green in byte 2, blue in lo byte
lsr.b #3,d7 ;right flush blue
moveq #0,d5
move.w (a1),d5 ;get dest pixel
add.w d5,d5 ;waste high bit
lsl.l #5,d5 ;but red in byte 3
lsr.w #3,d5 ;but green in byte 2, blue in lo byte
lsr.b #3,d5 ;right flush blue
move.l d7,d0 ;prime result with src
cmp.l d5,d0 ;is dst greater?
bhs.s @gotRed ;no, use src
move.l d5,d0 ;use dst value instead
@gotRed
move.w d7,d0 ;prime result with src
cmp.w d5,d0 ;is dst greater?
bhs.s @gotGreen ;no, use src
move.w d5,d0 ;use dst value instead
@gotGreen
move.b d7,d0 ;prime result with src
cmp.b d5,d0 ;is dst greater?
bhs.s @gotBlue ;no, use src
move.b d5,d0 ;use dst value instead
@gotBlue
lsl.b #3,d0 ;rejoin green/blue
lsl.w #3,d0 ;rejoin red/green/blue
lsr.l #6,d0 ;right flush red/green/blue
MOVE.w d0,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 47: MIN(PAT, DST) --> DST
;
;-------------------------------------------------------
; a0 = d0 = result
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slMin16
move.l d7,-(sp) ;preserve d7
BSR arithSetup16 ;set up registers for slab bitblt
@blit tst.w (a2)+ ;a pixel of the clip region
beq.s @skip
moveq #0,d7
move.w 0(a3,d6),d7 ;get src pixel
add.w d7,d7 ;waste high bit
lsl.l #5,d7 ;but red in byte 3
lsr.w #3,d7 ;but green in byte 2, blue in lo byte
lsr.b #3,d7 ;right flush blue
moveq #0,d5
move.w (a1),d5 ;get dest pixel
add.w d5,d5 ;waste high bit
lsl.l #5,d5 ;but red in byte 3
lsr.w #3,d5 ;but green in byte 2, blue in lo byte
lsr.b #3,d5 ;right flush blue
move.l d7,d0 ;prime result with src
cmp.l d5,d0 ;is dst smaller?
bls.s @gotRed ;no, use src
move.l d5,d0 ;use dst value instead
@gotRed
move.w d7,d0 ;prime result with src
cmp.w d5,d0 ;is dst smaller?
bls.s @gotGreen ;no, use src
move.w d5,d0 ;use dst value instead
@gotGreen
move.b d7,d0 ;prime result with src
cmp.b d5,d0 ;is dst smaller?
bls.s @gotBlue ;no, use src
move.b d5,d0 ;use dst value instead
@gotBlue
lsl.b #3,d0 ;rejoin green/blue
lsl.w #3,d0 ;rejoin red/green/blue
lsr.l #6,d0 ;right flush red/green/blue
MOVE.w d0,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;-------------------------------------------------------
;
; MODE 40: AVG(SRC, DST, WEIGHT) --> DST
;
; CLOBBERS: D0,D3,D2,A1,A2
; A3,D6 (BUT NOT IN FASTSLAB)
;-------------------------------------------------------
; a0 = /last dst d0 = red weight
; a1 = dstPtr d1 = blue/grn weight (scanCount)
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = /last src
; a4 = d4 = /last result
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 = src pixel
;-------------------------------------------------------
slAvg16
lea @slAvg16Slow,a4 ;assume, general blend16 from now on
lea weight(a6),a0 ;point to weights
move.w (a0)+,d5
cmp.w (a0)+,d5 ;is opColor gray?
bne.s @slAvg16Slow
cmp.w (a0),d5
bne.s @slAvg16Slow
addq #1,d5 ;yes, check for gray values of $8000 or $7fff
and.w #$fffe,d5
cmp.w #$8000,d5
bne.s @slAvg16Slow
lea @slAvg16Half,a4 ;use fast 50% blend16 from now on
bra @slAvg16Half
ALIGN Alignment
;-------------------------------------------------------
;
; General blend case for non 50% gray weights
;
;
@slAvg16Slow
move.l d7,-(sp) ;preserve d7
BSR arithSetup16 ;set up registers for slab bitblt
lea weight(a6),a0 ;point at blue weight
move.l (a0)+,d1 ;get blue/green weight
move.w (a0),d0 ;get red weight
@short0 moveq #0,d4 ;init last result
move.l d4,d3 ;init last src
move.l d4,a0 ;init last dst
@blit tst.w (A2)+ ;a pixel of the clip region
BEQ @skip
moveq #0,d7
move.w 0(a3,d6),d7 ;get src pixel
moveq #0,d5
move.w (a1),d5 ;get dest pixel
@short1 cmp.w d3,d7 ;same as last time?
bne.s @hardway ;no, go do it
cmp.w a0,d5 ;same as last time?
beq.s @again ;yes, go fast
@hardway
add.w d7,d7 ;waste high bit
lsl.l #5,d7 ;but red in byte 3
lsr.w #3,d7 ;but green in byte 2, blue in lo byte
lsr.b #3,d7 ;right flush blue
add.w d5,d5 ;waste high bit
lsl.l #5,d5 ;but red in byte 3
lsr.w #3,d5 ;but green in byte 2, blue in lo byte
lsr.b #3,d5 ;right flush blue
@blue moveq #0,d3 ;clr out high end
move.b d7,d3 ;get src blue
swap d1 ;get blue weight
mulu.w d1,d3 ;% blue
moveq #0,d4 ;clr out high end
move.b d5,d4 ;get dst blue
neg.w d1
mulu.w d1,d4 ;% blue
neg.w d1
add.l d3,d4 ;get 21 bits of blue
swap d4 ;right align 5 blue bits
move.l d4,a0 ;a0 has 000B
@grn move.w d7,d3 ;get src grn
lsr.w #8,d3
swap d1 ;get grn weight
mulu.w d1,d3 ;% grn
move.w d5,d4 ;get dst grn
lsr.w #8,d4
neg.w d1
mulu.w d1,d4 ;% grn
neg.w d1
add.l d3,d4 ;get 21 bits of grn
swap d4 ;right align 5 green bits
lsl.w #5,d4 ;shift into place
add.w d4,a0 ;a0 has 00GB
@red moveq #0,d3 ;clr out high end
swap d7
move.b d7,d3 ;get src red
mulu.w d0,d3 ;% red
moveq #0,d4 ;clr out high end
swap d5
move.b d5,d4 ;get dst red
neg.w d0
mulu.w d0,d4 ;% red
neg.w d0
add.l d3,d4 ;get 21 bits of red
clr.w d4 ;clear lsb's
lsr.l #6,d4 ;shift into place
add.w a0,d4 ;d4 has 0RGB
@short2 swap d5 ;get back dst
lsl.b #3,d5 ;rejoin green/blue
lsl.w #3,d5 ;rejoin red/green/blue
lsr.l #6,d5 ;right flush red/green/blue
move.l d5,a0 ;save for short circuit
swap d7 ;get back src
lsl.b #3,d7 ;rejoin green/blue
lsl.w #3,d7 ;rejoin red/green/blue
lsr.l #6,d7 ;right flush red/green/blue
move.l d7,d3 ;save for short circuit
@again MOVE.w d4,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w patHMask(a6),d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
move.l (sp)+,d7 ;restore d7
RTS
ALIGN Alignment
;--------------------------------------------
;
; Optimized 50% blend case for 16 bits/pixel
;
;-------------------------------------------------------
; a0 = low bit mask d0 = high bit mask
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 = lsb's of result
; a4 = d4 = patHMask
; a5 = d5 = dest pixel
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
@slAvg16Half
BSR arithSetup16 ;set up registers for slab bitblt
move.w #$3def,d0 ;get high bit clearing mask
move.w #$0421,a0 ;get low bit mask
@blit2 tst.w (A2)+ ;a pixel of the clip region
BEQ.S @skip2
move.w 0(a3,d6),d1 ;get src pixel
move.w a0,d3 ;copy low bit mask
and.w d1,d3 ;remember src lsb's
lsr.w #1,d1 ;get almost 1/2 of it
and.w d0,d1 ;mask out stragglers
move.w (a1),d5 ;get dest pixel
and.w d5,d3 ;compute carry out of lsb
lsr.w #1,d5 ;get almost 1/2 of it
and.w d0,d5 ;mask out stragglers
add.w d5,d1 ;merge src with dst
add.w d3,d1 ;propagate carrys
MOVE.w d1,(a1) ;write pattern to dest
@skip2 addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit2 ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;--------------------------------------------
;
; Mode: 36 Transparent for 16 bits/pixel
;
;-------------------------------------------------------
; a0 = d0 =
; a1 = dstPtr d1 = src pixel
; a2 = maskPtr d2 = run cnt
; a3 = patPtr d3 =
; a4 = d4 = patHMask
; a5 = d5 = backColor
; a6 = locals d6 = pattern offset
; a7 = d7 =
;-------------------------------------------------------
slTransparent16
BSR arithSetup16 ;set up registers for slab bitblt
move.l transColor(A6),D5 ;get a pixel of the transparent color
@blit tst.w (A2)+ ;a pixel of the clip region
BEQ.S @skip
move.w 0(a3,d6),d1 ;get src pixel
cmp.w d1,d5 ;is src backColor?
beq.s @skip ;yes, don't write to dst
MOVE.w d1,(a1) ;write pattern to dest
@skip addq.l #2,a1 ;bump dst ptr
addq.l #2,d6 ;bump src index
and.w d4,d6 ;constrict to the source long if in a pattern mode
DBRA D2,@blit ;LOOP ALL LONGS THIS ROW
RTS
ALIGN Alignment
;--------------------------------------------
;
; PROCEDURE SlabMode
;
; INPUT: D2: MODE, CLOBBERED
; OUTPUT: A4: MODECASE
;
; for arithmetic modes, also set up patHMask, patHPos
;
SlabMode
AND #$37,D2 ;toss all but arithmetic, hilite bits + variant bits
BCLR #5,D2 ;arithmetic mode?
BEQ.S @clrInvBit ;if so, dont clear the invert bit
BCLR #4,D2 ;hilite?
BEQ.S @skipHilite ;if not, dont add hilite offset
MOVEQ #8,D2 ;hilite is at $20, so put ($20 / 2) - 8 here
BRA.S @2 ; <SMC 26SEP90> <12>
@skipHilite
cmp #16,dstPix+pixelSize(A6) ;dst 16,32 bits/pixel?
bge @useLoops32 ;yes, use alternate table
@2 MOVE #$1F,patHMask(A6) ;set up patHMask for 1 long for small patterns
CMP #4,PATROW(A6) ;NEED EXPANDED PATTERN?
BLE.S @1 ;if not, all ready to go
MOVEM.L D2/D3,-(SP) ;save work registers
MOVE dstPix+pixelSize(A6),D3 ;get number of bits in a pixel
SUBQ #1,D3 ;make into a mask
NOT D3 ;turn on bits equal to & greater than pixelSize
MOVE patRow(A6),D2 ;get pattern row size
ASL #3,D2 ;convert from bytes to bits
SUBQ #1,D2 ;make it a mask
AND D3,D2 ;force pixel alignment
MOVE D2,patHMask(A6) ;save mask
MOVE patHPos(A6),D2 ;get pattern offset <BAL 17Jan89>
ASL #3,D2 ;convert from bytes to bits <BAL 17Jan89>
MOVE D2,patHPos(A6) ;save for arith setup <BAL 17Jan89>
MOVEM.L (SP)+,D2/D3 ;restore work registers
@1
cmp #16,dstPix+pixelSize(A6) ;dst 16,32 bits/pixel? <SMC 26SEP90> <12>
bge.s @useLoops32 ;yes, use alternate table <SMC 26SEP90> <12>
ADDQ #8,D2 ;point to arithmetic modes <SMC 26SEP90> <12>
;ciPatPrep (from QDciPatchROM.a) <sm 6/9/92>stb
if Quicker then
cmp #8,dstPix+pixelSize(A6) ;dst 8 bits/pixel?
blt.s @goTable ;yes, use alternate table <sm 6/9/92>stb
subq #8,d2 ;make average mode zero based
lea slArith8Tab,A4 ;point to 8 bit arithmetic mode table
add.l 0(A4,D2*4),A4 ;GET CASE JUMP ADDRESS
RTS
else
bra.s @goTable <sm 6/9/92>stb
endif
@clrInvBit
AND #$3,D2 ;GET LO 2 BITS OF MODE, clearing bit 4 also
BNE.S @4 ;if not a copy mode, skip over this stuff <17>
TST.B alphaMode(A6) ;are drawing in alpha mode? <17>
BEQ.S @4 ;no, use normal loops <17>
LEA slMASK8A,A4 ;get address of small pat alpha copy loop <17>
CMP #4,PATROW(A6) ;large pattern? <17>
BLE.S @3 ;no, exit <17>
LEA slXMASK8A,A4 ;yes, use big pattern copy loop <17>
@3 RTS ; <17>
@4 CMP #4,PATROW(A6) ;NEED EXPANDED PATTERN?
BLE.S @goTable ;=>NO <sm 6/9/92>stb
ADDQ #4,D2 ;ELSE BUMP TO EXPANDED ROUTINES
@goTable ; <sm 6/9/92>stb
LEA SlabModeTab,A4 ;POINT TO MODE TABLE
MOVE.L 0(A4,D2*4),A4 ;GET CASE JUMP ADDRESS
RTS
@useLoops32
beq.s @useLoops16
move.l slArith32TabPtr,A4 ;POINT TO MODE TABLE
add.l 0(A4,D2*4),A4 ;GET CASE JUMP ADDRESS
RTS
@useLoops16
move.l slArith16TabPtr,A4 ;POINT TO MODE TABLE
add.l 0(A4,D2*4),A4 ;GET CASE JUMP ADDRESS
MOVE PATHMASK(A6),D2 ;GET HORIZ MASK
bset #1,d2 ;make into word mask
MOVE d2,PATHMASK(A6) ;put HORIZ MASK
RTS
IF 0 THEN
MODETAB DC.W MODETAB-MASK8
DC.W MODETAB-MASK9
DC.W MODETAB-MASK10
DC.W MODETAB-MASK11
DC.W MODETAB-XMASK8
DC.W MODETAB-XMASK9
DC.W MODETAB-XMASK10
DC.W MODETAB-XMASK11
DC.W ModeTab-Avg ;10 AVG(PAT, DST, WEIGHT) --> DST
DC.W ModeTab-AddPin ;12 PAT + DST --> DST (pin to max)
DC.W ModeTab-AddOver ;13 PAT + DST --> DST (no pin)
DC.W ModeTab-SubPin ;16 DST - PAT --> DST (pin to min)
DC.W ModeTab-Transparent ;18 PAT less bg --> DST
DC.W ModeTab-Max ;1A MAX(PAT, DST) --> DST
DC.W ModeTab-SubOver ;1C DST - PAT --> DST (no pin)
DC.W ModeTab-Min ;1E MIN(PAT, DST) --> DST
DC.W ModeTab-Hilite ;20 (pat as mask) hilite <--> background
ENDIF
Align 4
if Quicker then
IMPORT slAddOver8
IMPORT slSubOver8
IMPORT slAddPin8
IMPORT slSubPin8
IMPORT slMax8
IMPORT slMin8
IMPORT slAvg8,slTransparent8
slArith8Tab
DC.L slAvg8-slArith8Tab ;10 AVG(PAT, DST, WEIGHT) --> DST
DC.L slAddPin8-slArith8Tab ;12 PAT + DST --> DST (pin to max)
DC.L slAddOver8-slArith8Tab ;13 PAT + DST --> DST (no pin)
DC.L slSubPin8-slArith8Tab ;16 DST - PAT --> DST (pin to min)
DC.L slTransparent8-slArith8Tab ;18 PAT less bg --> DST
DC.L slMax8-slArith8Tab ;1A MAX(PAT, DST) --> DST
DC.L slSubOver8-slArith8Tab ;1C DST - PAT --> DST (no pin)
DC.L slMin8-slArith8Tab ;1E MIN(PAT, DST) --> DST
DC.L slHilite-slArith8Tab ;20 MIN(PAT, DST) --> DST
endif
slArith16Tab
DC.L slAvg16-slArith16Tab ;10 AVG(PAT, DST, WEIGHT) --> DST
DC.L slAddPin16-slArith16Tab ;12 PAT + DST --> DST (pin to max)
DC.L slAddOver16-slArith16Tab ;13 PAT + DST --> DST (no pin)
DC.L slSubPin16-slArith16Tab ;16 DST - PAT --> DST (pin to min)
DC.L slTransparent16-slArith16Tab ;18 PAT less bg --> DST
DC.L slMax16-slArith16Tab ;1A MAX(PAT, DST) --> DST
DC.L slSubOver16-slArith16Tab ;1C DST - PAT --> DST (no pin)
DC.L slMin16-slArith16Tab ;1E MIN(PAT, DST) --> DST
DC.L slHilite-slArith16Tab ;20 (pat as mask) hilite <--> background
slArith32Tab
DC.L slAvg32-slArith32Tab ;10 AVG(PAT, DST, WEIGHT) --> DST
DC.L slAddPin32-slArith32Tab ;12 PAT + DST --> DST (pin to max)
DC.L slAddOver32-slArith32Tab ;13 PAT + DST --> DST (no pin)
DC.L slSubPin32-slArith32Tab ;16 DST - PAT --> DST (pin to min)
DC.L slTransparent32-slArith32Tab ;18 PAT less bg --> DST
DC.L slMax32-slArith32Tab ;1A MAX(PAT, DST) --> DST
DC.L slSubOver32-slArith32Tab ;1C DST - PAT --> DST (no pin)
DC.L slMin32-slArith32Tab ;1E MIN(PAT, DST) --> DST
DC.L slHilite-slArith32Tab ;20 (pat as mask) hilite <--> background
ALIGN Alignment
;---------------------------------------------------------------
;
; FAST LOOPS, OPTIMIZED FOR SOLID PATTERN AND RECTANGLE CLIPPED
;
; FAST FOREGROUND SLAB:
;
FAST11 MOVE.L D5,D4 ; <sm 6/9/92>stb
TST D2 ; <sm 6/9/92>stb
FAST8 BEQ.S MERGE8 ;BR IF ALL IN ONE LONG
MOVE.L D3,D0 ;GET LEFTMASK
NOT.L D0 ;GET NOT LEFTMASK
AND.L (A1),D0 ;PUNCH OUT DST
AND.L D4,D3 ;OR FGCOLOR INTO LEFTMASK
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;AND PUT TO DST
SUB #2,D2 ;ADJUST LONGCOUNT FOR DBRA
BLT.S LAST8 ;BR IF NO UNMASKED LONGS
LOOP8 MOVE.L D4,(A1)+ ;WRITE A LONG OF FOREGROUND
DBRA D2,LOOP8 ;LOOP ALL UNMASKED LONGS
BRA.S LAST8 ;GO DO LAST LONG
MERGE8 AND.L D3,D1 ;COMBINE LEFTMASK AND RIGHTMASK
LAST8 MOVE.L D1,D0 ;GET MASK
AND.L D4,D0 ;APPLY FGCOLOR TO MASK
NOT.L D1 ;GET NOTMASK
AND.L (A1),D1 ;PUNCH OUT DST
OR.L D1,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;OR RIGHTMASK INTO DST
RTS ;AND RETURN
ALIGN Alignment
;
; FAST XOR SLAB:
;
FAST10 BEQ.S MERGE10 ;BR IF ALL IN ONE LONG
EOR.L D3,(A1)+ ;XOR LEFTMASK INTO DST
SUB #2,D2 ;ADJUST LONGCOUNT FOR DBRA
BLT.S LAST10 ;BR IF NO UNMASKED LONGS
LOOP10 NOT.L (A1)+ ;INVERT A LONG OF DST
DBRA D2,LOOP10 ;LOOP ALL UNMASKED LONGS
LAST10 EOR.L D1,(A1)+ ;XOR RIGHTMASK INTO DST
RTS ;AND RETURN
MERGE10 AND.L D3,D1 ;COMBINE LEFTMASK AND RIGHTMASK
EOR.L D1,(A1)+ ;XOR RIGHTMASK INTO DST
RTS ;AND RETURN
IF 0 THEN ;•••
ALIGN Alignment
; FAST BACKGROUND SLAB:
FAST11 BEQ.S MERGE11 ;BR IF ALL IN ONE LONG
MOVE.L D3,D0 ;GET LEFTMASK
NOT.L D0 ;GET NOT LEFTMASK
AND.L (A1),D0 ;PUNCH OUT DST
AND.L D5,D3 ;OR BKCOLOR INTO LEFTMASK
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;AND PUT TO DST
SUB #2,D2 ;ADJUST LONGCOUNT FOR DBRA
BLT.S LAST11 ;BR IF NO UNMASKED LONGS
LOOP11 MOVE.L D5,(A1)+ ;WRITE A LONG OF BACKGROUND
DBRA D2,LOOP11 ;LOOP ALL UNMASKED LONGS
BRA.S LAST11 ;GO DO LAST LONG
MERGE11 AND.L D3,D1 ;COMBINE LEFTMASK AND RIGHTMASK
LAST11 MOVE.L D1,D0 ;GET MASK
AND.L D5,D0 ;APPLY BKCOLOR TO MASK
NOT.L D1 ;GET NOTMASK
AND.L (A1),D1 ;PUNCH OUT DST
OR.L D1,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;OR RIGHTMASK INTO DST
RTS ;AND RETURN
ENDIF ;•••
ALIGN Alignment
; FAST FOREGROUND/BACKGROUND SLAB USING ALPHA MASK: <17>
FAST11A MOVE.L D5,D4 ;USE BKCOLOR INSTEAD OF FGCOLOR
FAST8A MOVE.L alphaMask(A6),D0 ;GET ALPHA MASK
AND.L D0,D1 ;CLIP LEFTMASK WITH ALPHAMASK
AND.L D0,D3 ;CLIP RIGHTMASK WITH ALPHAMASK
MOVE.L D0,A0 ;save copy of alpha mask
TST D2 ;RETEST THE LONG COUNT
BEQ.S MERGE8A ;BR IF ALL IN ONE LONG
MOVE.L D3,D0 ;GET LEFTMASK
NOT.L D0 ;GET NOT LEFTMASK
AND.L (A1),D0 ;PUNCH OUT DST
AND.L D4,D3 ;OR FGCOLOR INTO LEFTMASK
OR.L D3,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;AND PUT TO DST
SUB #2,D2 ;ADJUST LONGCOUNT FOR DBRA
BLT.S LAST8A ;BR IF NO UNMASKED LONGS
MOVE.L A0,D3 ;GET CENTER MASK
NOT.L D3 ;GET NOT OF MASK
LOOP8A MOVE.L (A1),D0 ;GET THE DST
EOR.L D4,D0 ;APPLY FGCOLOR
AND.L D3,D0 ;MASK OUT PART OF DST
EOR.L D4,D0 ;REAPPLY FGCOLOR
MOVE.L D0,(A1)+ ;AND PUT TO DST
DBRA D2,LOOP8A ;LOOP ALL UNMASKED LONGS
BRA.S LAST8A ;GO DO LAST LONG
MERGE8A AND.L D3,D1 ;COMBINE LEFTMASK AND RIGHTMASK
LAST8A MOVE.L D1,D0 ;GET RIGHTMASK
NOT.L D0 ;GET NOT RIGHTMASK
AND.L (A1),D0 ;PUNCH OUT DST
AND.L D4,D1 ;OR FGCOLOR INTO RIGHTMASK
OR.L D1,D0 ;COMBINE SRC AND DST
MOVE.L D0,(A1)+ ;AND PUT TO DST
RTS ;AND RETURN
ALIGN Alignment
; FAST XOR SLAB USING ALPHA MASK: <17>
FAST10A MOVE.L alphaMask(A6),D0 ;GET ALPHAMASK
AND.L D0,D1 ;CLIP LEFTMASK WITH ALPHAMASK
AND.L D0,D3 ;CLIP RIGHTMASK WITH ALPHAMASK
TST D2 ;RETEST THE LONG COUNT
BEQ.S MERGE10A ;BR IF ALL IN ONE LONG
EOR.L D3,(A1)+ ;XOR LEFTMASK INTO DST
SUB #2,D2 ;ADJUST LONGCOUNT FOR DBRA
BLT.S LAST10A ;BR IF NO UNMASKED LONGS
LOOP10A EOR.L D0,(A1)+ ;INVERT A LONG OF DST
DBRA D2,LOOP10A ;LOOP ALL UNMASKED LONGS
LAST10A EOR.L D1,(A1)+ ;XOR RIGHTMASK INTO DST
RTS ;AND RETURN
MERGE10A AND.L D3,D1 ;COMBINE LEFTMASK AND RIGHTMASK
EOR.L D1,(A1)+ ;XOR RIGHTMASK INTO DST
RTS ;AND RETURN
ALIGN Alignment
;--------------------------------------------------------------------
;
; PROCEDURE FastSlabMode, Call when rect clipped and pattern black.
;
; INPUT: D2: MODE, CLOBBERED mode 0=black, 1=xor, 2=white
; OUTPUT: A4: MODECASE
;
; This code has the improvements from QDciPatchROM.a
FastSlabMode
AND #$3,D2 ;GET LO 2 BITS OF MODE
TST.B alphaMode(A6) ;are we drawing in alpha mode? <17>
BEQ.S @1 ;no, use original fast cases <17>
ADDQ #3,D2 ;no, use new fast cases <18>
@1 LEA FASTTAB,A4 ;POINT TO MODE TABLE
SUB.W 0(A4,D2*2),A4 ;GET OFFSET FROM FASTTAB <18>
RTS
FASTTAB DC.W FASTTAB-FAST8 ;BLACK
DC.W FASTTAB-FAST10 ;XOR
DC.W FASTTAB-FAST11 ;WHITE
DC.W FASTTAB-FAST8A ;alpha BLACK (foreground) <17>
DC.W FASTTAB-FAST10A ;alpha XOR <17>
DC.W FASTTAB-FAST11A ;alpha WHITE (background) <17>
COPYHANDLE PROC EXPORT
IMPORT RSetHSize
;----------------------------------------------------------
;
; PROCEDURE COPYHANDLE (SRCH,DSTH: Handle);
;
; Copies SRCH into DSTH, resizing it if necesary.
; OK if srcH is purgeable. <1.7> BAL
;
PARAMSIZE EQU 8
SRCH EQU PARAMSIZE
DSTH EQU SRCH-4
MOVE.L SRCH(SP),D0 ; GET SRC HANDLE
BEQ.S DONE ; =>EXIT IF NO SRC
MOVE.L D0,A0 ; A0 = SRCH
MOVE.L DSTH(SP),D0 ; GET DST HANDLE
BEQ.S DONE ; =>EXIT IF NO DST
MOVE.L D0,A1 ; A1 = DSTH
_HGetState ; get src purge/lock state <1.7> BAL
move.b d0,-(sp) ; save for later restore <1.7> BAL
_HNoPurge ; don't let it purge <1.7> BAL
_GetHandleSize ; D0 = size of SRCH
MOVE.L D0,D1 ; save size in D1
EXG A0,A1 ; get DSTH in A0
JSR RSetHSize ; make it the same size
EXG A0,A1 ; A0 = SRCH, A1 = DSTH
move.b (sp)+,d0 ; get saved state <1.7> BAL
_HSetState ; restore it <1.7> BAL
MOVE.L (A0),A0 ; get SRC pointer
MOVE.L (A1),A1 ; get DST pointer
MOVE.L D1,D0 ; D0 = size
_BlockMove ; copy the data
DONE MOVE.L (SP)+,A0 ; get return address
ADDQ #8,SP ; strip parameters
JMP (A0) ; and return
ENDPROC