TweetFollow Us on Twitter

Spiffy Color 2
Volume Number:6
Issue Number:12
Column Tag:Color Workshop

Related Info: Color Quickdraw

Spiffy Color Demo

By John A. Love, III, Springfield, VA

Spiffy Color Effects Demo

Part II

[John is a member of theWashington Apple Pi Users’ Group from the greater Washington D.C. metropolitan area and can be reached on Applelink {D3471} and on GEnie {J.LOVE7}]

Although the application file on the MacTutor disk is named “Rotation Demo”, the color effects illustrated are more inclusive, as follows:

a) Rotation.

b) Dissolve.

c) Text Scrolling & Un-Rolling. Select the “About ...” Menu item to observe these.

d PICT/PICT2 scrolling.

e Just for hex, press “z” or “Z” and enjoy!!

In addition, you’ll observe color menus, color windows, color icons, color Scroll Bars, color CuRSoRs and rotating CURSors (sorry, the latter are in “yucky” black-and-white). Finally, you’ll listen to the joyous sound of Macintosh Developer Tech Support’s (MacDTS) mascot, DogCow™. All of this is in a MultiFinder™-aware demo package.

By the way, this daggum demo has successfully run on a:

• Mac IIx with Apple’s standard color monitor

• Mac IIci with Raster Op’s monitor & their 24-bit color card { will miracles never cease ????? }

• MacIIci mated with Radius’ Two Page Display and Apple’s standard color monitor, with my window entirely on one or the other. Pleeeeese don’t ask about my window overlapping both !!!!!

As I stipulated last month, because of length restrictions, I postponed the presentation of both the Assembly code and the “RMaker” source code. The former presents the pivotal routines used to rotate and dissolve bit images, whether they be in color or in black-and-white. I placed them in an external library for the THINK© Pascal {version 3.Ø} Project. As I also mentioned last month, I used my all-time favorite Assembler, McAssembly™, authored by Dave McWherter and formerly distributed by Signature Software. To me, the most enticing feature of this particular Assembler is what Dave calls his Trap Compiler wherein one is not burdened by the sometimes-repetitive pushes onto the Stack inherent to almost every PROCEDURE / FUNCTION call and pops from the Stack for every FUNCTION call. Dave’s Trap Compiler allows the programmer to write just ONE line of code, just as in Pascal ---- you heard me, just ONE !!!

First below is all the Assembly stuff, followed by the ‘RMaker’ source. Enjoy !!!!!

The first are the two macro files used by Dave McWherter’s “McAssembly” for:

(a) Linkage to external routines

(b) Stack pushing & poping

Then, we see my color extensions of two routines originally written in Assembly for the black-and-white world:

(a) John Olsen’s rotation scheme [MacTutor, Feb 88]

(b) Mike Morton’s dissolve routine [MacTutor, Dec 85] ]

NOTE: I’ve provided prolific comments in the source code to help you follow the logic.

Listing: LinkMacros.asm

 iflist 0 ; Do NOT list un-assembled
 ;   statements [optional].


;***********************************************
; "LinkMacros.asm"
: -- Some macros to handle Procedures & Functions:
;
; Note: a "loc" clears ALL local parameters 
;       from memory and starts fresh.
;***********************************************


proc    macrox
 loc
 pframe
 endm
;--------------
; First, determine size of the result
; and THEN set up the parameter frame:
func    macrox &1
 loc  
 
 dsec 0
.getSize&1
 
 if&&1 = "byte"
 byte   ; Align to word boundary.  
 endi
 
 dend .sizeResult
 
 pframe
.result byte.sizeResult
 endm
;--------------  
endParmsmacrox
 endp .parambytes
 endm
;--------------  
noParms macrox
 endp .parambytes
 endm
;--------------  
locals  macrox

 ifndef .parambytes; Just in case you forgot !!
 endParms
 endi
 
 lframe
 endm
;--------------  
endLocals macrox
 endl .localbytes
 endm
;--------------
noLocalsmacrox
.localbytes set  0
 endm
;--------------
enter   macrox

 ifndef .parambytes; Just in case you forgot !!
 endParms
 endi
 
 ifndef .localbytes; Just in case you forgot !!
 noLocals
 endi
 
 if.parambytes <> 0 OR .localbytes <> 0 
 link a6,#-.localbytes
 endi
 
 endm
;--------------
exit    macrox   ; If a Function, result
 ;   stays on the Stack !!
 
 if.parambytes <> 0 OR .localbytes <> 0 
 unlk a6
 endi
 
 ifndef .sizeResult; a PROCEDURE.
.sizeResult set  0
 endi
 
 if.parambytes <> 0
 move.l (sp)+,a0
 addi.l #.parambytes-.sizeResult,sp
 jmp  (a0)
 else
 rts
 endi
 
 endm

;***********************************************
; These allow calls to be structured as follows:
;***********************************************
;
;aFunct funclong
;.var1  integer  ; Optional stack variables go here.
;.var2  var
;endParms
;
;locals
;.var3  boolean  ; Optional local variables go here.
;.var4  long
;endLocals
;
;      [On entry, do the link (if necessary).  Upon
;  exit, unlink (if necessary) & then return.
;The actual code, of course, goes inbetween.
;IF the "bsr" call is to a Function, be sure
;to "move" from (sp)+ to a location of your
;choice AFTER you return from the "bsr" call.]
;
;enter
;
;exit
;
;***********************************************
;
;aProc  proc
;noParms; Optional.
;noLocals ; Optional.
;
;enter
;
;exit
;
;***********************************************
;
;Anotherproc
;.var1  handle
;.var2  pointer
;endParms
;
;noLocals ; Optional.
;
;enter
;
;exit

Listing: rotAsm.asm

; "rotAsm.asm"
; -- contains two external routines for my "rotAsm.Lib":
;
; #1) "RotateBits.asm"
;     -- a routine originally designed to rotate text 90-degrees CCW 
on the screen
;
;     Written in 68000 Code by John D. Olsen [MacTutor (Feb 88)]
;     and optimized by Mike Morton [MacTutor (Nov 88)]
;
; ********************
;
; #2) "DissBits.asm"
;     -- a routine to create a Dissolve-effect on the screen
;     -- alias "My kingdom for another Register !!"
;
;    I know this blasted routine works, but ...
;    ... in 3 novels or less, PLEASE tell me WHY ?*!!?
;    ... { "just because" is NOT an acceptable reply }
;
;    Written in 68000 Code by Mike Morton [MacTutor (Dec 85)]
;
; ********************
;
; Converted to color (we hope!!) by
; John A. Love, III [Washington Apple Pi Users' Group]
;
; [ using "McAssembly" (v7.3) from Signature Software ]


;****************************************************************
; The parts of my HFS Path Names:

volName define "HD"
AsmFolder define "McAsm Folder"
generalFolder  define"General  Files  Folder"

;****************************************************************


; INCLUDE files : RegisterTraps.PSM
;  RegisterTrapMacros.asm
;  ToolEqu.PSM
;  QuickEqu.PSM
;  SysEqu.PSM
;  SysErr.PSM
;  PushPop.asm
;  LinkMacros.asm
;
;   with LISTing turned off.
 

 LIST 0   ; OFF.
 
 ipath  "{volName}:{AsmFolder}:{generalFolder}:Boot TRAPs Folder:"
 incl "RegisterTraps.PSM"
 incl "RegisterTrapMacros.asm"
;  PAGE   ; Eliminated in final version.
 
 ipath  "{volName}:{AsmFolder}:{generalFolder}:Boot EQUates Folder:"
 incl "ToolEqu.PSM"
 incl "QuickEqu.PSM"
 incl "SysEqu.PSM"
 incl "SysErr.PSM"
 
 ipath  "{volName}:{AsmFolder}:{generalFolder}:Boot MACROs Folder:"
 incl "PushPop.asm"
;  PAGE   ; Eliminated in final version.
 incl "LinkMacros.asm"
;  PAGE   ; Eliminated in final version.
 
 LIST 1   ; Back ON.


 TCOMP  ; Turn on the Trap Compiler.

 page

 XDEF RotateBits,DissBits
;XREF TestForColor ; Included here for historical reasons.

 
 
; FUNCTION  RotateBits (srcBits, dstBits: BitMap): OSErr;
;   Assumes mode = srcCopy + NO masking:

RotateBitsfunc integer
.srcBitspointer  ; --> BitMaps or PixMaps ...
.dstBitspointer
 endParms
; ~~~~~~~~~~~~~
 locals
.lowLeftAddrpointer
.rowCount integer
.byteCountinteger
.srcBaseAddrpointer
.srcBoundsBits integer    ; Bits across rect.
.srcBoundsrect
.colorExistsboolean; Color stuff ...
.pixelSizeinteger
.pixelBit integer
 endLocals
; ~~~~~~~~~~~~~
; Our Working Registers:

.srcPtr requa2   ; Passed parameters ...
.dstPtr requa3
; -----
.currWordAddr  requa4; Other worker bees ...
.width2 requd0   ; Width/2 of Source.
.height2requd1   ; Height/2 of Source.
.centerVrequd2
.centerHrequd3
.topLeftrequd4
.botRight requ d5
.rowBytesDest  requd6; ... of rotated Destination's BitMap.
; -----
.rowBitCounter requd0
.wordBitCntrrequ d1
.rowCounter requ d2
.colBitCounter requd3
.currWordSrcrequ d4
.pixelCounter  requd5
.srcRowBytesrequ d7; Keep D6 safe ( = .rowBytesDest ).

 page

 enter
 
 
 movem.la0-a5/d0-d7,-(sp) ; Deposit your life savings.
 ; ==========

 ; Create an off-screen BitMap Record
 ; wherein the text will be saved:
 
 move.l .srcBits,.srcPtr
 move.l .dstBits,.dstPtr
 
 ; ----------
 ; Do some preliminary setup for Color:
 ; ----------
 
 clr.w  -(sp)
 bsr  TestForColor
 pop.w  .colorExists
 
 move.w #1,.pixelSize; Assume black-and-white.
 tst.b  .colorExists
 beq.s  .bW
 ;
.color  GetGDevice =a1    ; Handle -->
 move.l (a1),a1  ;   Pointer.
 move.l gdPMap(a1),a0; Ditto ...
 move.l (a0),a0
 move.w pmPixelSize(a0),.pixelSize
 ;
.bWmove.l baseAddr(.srcPtr),.srcBaseAddr
 move.w rowBytes(.srcPtr),.srcRowBytes
 andi.w #$3FFF,.srcRowBytes ; Strip top 2 bits for Color calculations.
 ;   ( already 0 for B&W )
 move.l bounds+topLeft(.srcPtr),.srcBounds+topLeft
 move.l bounds+botRight(.srcPtr),.srcBounds+botRight
 
 ; ----------
 ; Height of Source becomes width of Destination:
 ; ----------
 
 move.w .srcBounds+bottom,.rowBytesDest; Bottom - Top.
 sub.w  .srcBounds+top,.rowBytesDest
 push.w .rowBytesDest
 mulu .pixelSize,.rowBytesDest
 addi.w #15,.rowBytesDest ; + some slop for rounding.
 
 ; Divide by 16 to convert to word-count in order
 ; to make "rowBytes" a multiple of four(4) bytes:
 
 lsr.w  #4,.rowBytesDest
 btst #0,.rowBytesDest  ; Round-up to even #.
 beq.s  .1; Already an even #.
 addq.w #1,.rowBytesDest
.1 lsl.w#1,.rowBytesDest

 ; ----------
 ; Now, compute the dstRect by rotating the srcRect 90-degrees CCW about
 ; the source's center.  No big deal here -- but, a BIG deal does come
 ; later when we compute the baseAddr of the rotated bit image.
 ;
 ; This OH-OH can be illustrated best by looking at the worst case wherein:
 ;
 ;    srcRowBytes*8 = (srcBounds.right - srcBounds.left) + 15
 ;
 ; This is because of the requirement that rowBytes be an even # of bytes
 ; and, preferably, an even # of words.  For this worst case, AFTER
 ; rotation, the top 15 rows are blank, thus effectively pushing the
 ; rotated image DOWN.  This problem is compounded further in that what
 ; I rotate next is the just-rotated image with its top 15 rows blank 
...
 ; thus, with the 2nd rotation, the image is also pushed RIGHT.  In short,
 ; only after four(4) 90-degree rotations, are we square, so-to-speak.
 ;
 ; One solution is simply to push DOWN the baseAddr of dstBits so these
 ; blank rows do NOT appear.  However, more on this sleight-of-hand later:
 ; ----------
 
 pop.w  .height2 ; = (bottom - top) from above.
 lsr.w  #1,.height2
 move.w .srcBounds+top,.centerV
 add.w  .height2,.centerV ; = top + height/2.
 ;
 move.w .srcBounds+right,.width2
 sub.w  .srcBounds+left,.width2
 lsr.w  #1,.width2
 move.w .srcBounds+left,.centerH
 add.w  .width2,.centerH  ; = left + width/2.
 ;
 move.w .centerV,.topLeft
 sub.w  .width2,.topLeft
 swap .topLeft   ; High word = top.
 move.w .centerH,.topLeft
 sub.w  .height2,.topLeft ; Low word = left.
 ;
 move.w .centerV,.botRight
 add.w  .width2,.botRight
 swap .botRight  ; High word = bottom.
 move.w .centerH,.botRight
 add.w  .height2,.botRight; Low word = right.

 ; ----------
 ; Assign data to dstBits directly.  Rather than push the
 ; baseAddr down as described above, why not avoid the problem
 ; altogether by rotating ONLY those bits in the width of
 ; srcBounds and NOT the number of bits in srcRowBytes ??
 ; ----------
 
 move.w .srcBounds+right,d0 ; height pixels ...
 sub.w  .srcBounds+left,d0
 ;
 mulu .pixelSize,d0; --> height bits.
 move.w .srcRowBytes,d1
 lsl.w  #3,d1
 cmp.w  d0,d1    ; Arrgh !!
 bhi.s  .2
 move.w d1,d0    ; I lied !!
.2 move.w d0,.srcBoundsBits
 divu .pixelSize,d0; ... back to height pixels.
 ;
 mulu .rowBytesDest,d0    ; X  width of destination.
 push.l d0; Save for later ...
 _NewHandle,clear
 move.w #noErr,.result    ; Assume everything's cool !!
 tst.w  d0
 beq.s  .3
 move.w #memFullErr,.result
 bra  .end
.3 _MoveHHi
 _HLock
 move.l (a0),baseAddr(.dstPtr)
 move.w .rowBytesDest,rowBytes(.dstPtr)
 tst.b  .colorExists
 beq.s  .blackWhite
 ;
 ori.w  #$8000,rowBytes(.dstPtr)
 ;
.blackWhite move.l .topLeft,bounds+topLeft(.dstPtr)
 move.l .botRight,bounds+botRight(.dstPtr)

 ; ----------
 ; Start the actual text rotation by first computing
 ; the address of the lower left corner of .dstBits.
 ; This maps from the upper left corner of .srcBits:
 ; ----------
 
 pop.l  d0; Total BitMap size ...
 sub.l  .rowBytesDest,d0  ; Minus last row's worth.
 add.l  (a0),d0
 move.l d0,.lowLeftAddr
 
 ; Initialize 2nd outermost loop counter:
 
 move.w .srcBounds+bottom,d0
 sub.w  .srcBounds+top,d0
 move.w d0,.rowCount ; = total Source rows.
 ;
 clr.w  .rowCounter
 
 move.l .srcBaseAddr,.srcPtr; --> Source's Bit Image.
 ; _Debugger; Yuck !!
 
.colLoopmove.w #16-1,.colBitCounter
 ; //////////
.colBitLoop move.l .lowLeftAddr,.currWordAddr
 cmpi.w #7,.colBitCounter
 bhi.s  .hiByte
 ;
.loByte addq.l #1,.currWordAddr
 ;
.hiByte move.w #0,.byteCount
 clr.w  .rowBitCounter
 
 ; ~~~~~~~~~~
.rowLoopmove.w (.srcPtr)+,.currWordSrc
 addq.w #2,.byteCount; = an even #.
 move.w #16-1,.wordBitCntr
 
 ; ----------
 move.w .colBitCounter,.pixelCounter ; Initialize ...
 move.w .pixelSize,.pixelBit
 
.wordLoop addq.w #1,.rowBitCounter
 cmp.w  .srcBoundsBits,.rowBitCounter
 bhi.s  .doneWithSrcWord
 ;
.nextBitadd.w  .currWordSrc,.currWordSrc
 bcc.s  .noBitToChange    ; Looks @ left-most bit.
 ;
 bset .pixelCounter,(.currWordAddr); MOD 8.
 ;
.noBitToChange subq.w#1,.pixelBit
 beq.s  .upOneRow
 subq.w #1,.pixelCounter
 bra.s  .sameRow
.upOneRow move.w .colBitCounter,.pixelCounter      ; Re-initialize ...
 move.w .pixelSize,.pixelBit
 sub.l  .rowBytesDest,.currWordAddr; Up one row and
.sameRowdbra.wordBitCntr,.wordLoop ;   over one Bit/Pixel.
 ; ----------
 
.doneWithSrcWord
 cmp.w  .byteCount,.srcRowBytes
 bhi.s  .rowLoop
 ; ~~~~~~~~~~
 
.doneWithSrcRow
 addq.w #1,.rowCounter
 cmp.w  .rowCount,.rowCounter
 beq.s  .end
 ;
 sub.w  .pixelSize,.colBitCounter
 bcc.s  .colBitLoop
 ; //////////
.doneWithDestWord
 addq.l #2,.lowLeftAddr
 bra.s  .colLoop

 ; ==========
.end    movem.l  (sp)+,a0-a5/d0-d7 ; Withdraw all your savings.
 

 exit

 page

; ======================================
; PROCEDURE  DissBits (srcBits, dstBits: BitMap; srcRect, dstRect: Rect);
;   Assumes mode = srcCopy + NO masking:

Dissbitsproc
.srcBitslong; --> BitMaps or PixMaps ...
.dstbitslong
.srcRectpointer  ; to Rectangles ...
.dstRectpointer
 endParms
; ~~~~~~~~~~~~~
 dsec 0 ; Our special Record.
.ourRowsword; Last row# and column# of inner
.ourColsword;   Rectangle [normalized to 0].
.ourLbits word   ; Ignored Bits in 1st Byte of Rect.
.ourStrideword   ; rowBits in bitMap.
.ourBasepointer  ; ... to 1st Byte in inner Rect.
 dend .ourSize
; ~~~~~~~~~~~~~
 locals
.srcOursbyte.ourSize
.dstOursbyte.ourSize
 endLocals
; ~~~~~~~~~~~~~
; Our Working Registers:

convertOK requ d0; Result from calling Convert.
strideWidth requ d0; Result from calling BitWidth.
; ----------
widthSrcrequd1   ; Bit-widths ...
heightSrc requ d0
totalWidthrequ d0; Total Bit-width = rows + columns.
pixWide requa2
; ----------
MaskByterequd3   ; Masks ...
cyMaskByterequ d0
bitMask requd5
; ----------
temp    requd2   ; Just temporary, folks !!
; ----------
srcAdr1Bitrequ a0; Address of 1st set Bit ...
dstAdr1Bitrequ a1
srcAdr1Byte requ a0; Address of 1st Byte ...
dstAdr1Byte requ a1
; ----------
srcLOGstriderequ d0; LOG, Base 2 ...
dstLOGstriderequ d1

 page

 enter
 
 
 movem.ld1-d7/a0-a5,-(sp) ; Deposit your life savings.
 ; ----------
 HideCursor ; Do our "magic" with Cursor hidden.

 ; ----------
 ; Convert input parms to our special format:

 clr.w  -(sp)    ; FUNCTIONal result.
 push.l .srcBits
 push.l .srcRect
 pea  .srcOurs ; VAR.
 bsr  Convert
 pop.w  convertOK
 beq  .end; Height or Width of Rectangle = 0.
 clr.w  -(sp)
 push.l .dstBits
 push.l .dstRect
 pea  .dstOurs ; VAR.
 bsr  Convert
 pop.w  convertOK
 beq  .end; Oh-Oh !!
 
 ; ----------
 ; Check that the two rectangles match in size:

 move.w .srcOurs+.ourRows,d0; First, the height ...
 cmp.w  .dstOurs+.ourRows,d0
 bne  .end
 move.w .srcOurs+.ourCols,d1; ... then, the width.
 cmp.w  .dstOurs+.ourCols,d1
 bne  .end
 
 ; ----------
 ; Determine bit-width needed to span rows & columns:
 
 clr.w  -(sp)    ; FUNCTIONal result.
 move.w .srcOurs+.ourCols,d0
 ext.l  d0
 push.l d0
 bsr  BitWidth
 pop.w  widthSrc ; Keep this sucker safe !!
 bne.s  .1; Falls thru if tiny width.
 CopyBits   .srcBits,.dstBits,.srcRect,.dstRect,#srcCopy,#0
 bra  .end
 ; ----------
.1 clr.w-(sp)    ; FUNCTIONal result.
 move.w .srcOurs+.ourRows,d0
 ext.l  d0
 push.l d0
 bsr  BitWidth
 pop.w  heightSrc
 bne.s  .2; Falls thru if very small height.
 CopyBits   .srcBits,.dstBits,.srcRect,.dstRect,#srcCopy,#0
 bra  .end
 
 ; ----------
 ; Setup some constants we'll need later:
 
.2 ext.lwidthSrc
 move.l #1,bitMask
 lsl.l  widthSrc,bitMask
 subq.l #1,bitMask ; All Bits are SET.
 ; ----------
 add.w  widthSrc,heightSrc
 move.w heightSrc,totalWidth
 ; ----------
 lea  MaskTable,a0
 clr.l  MaskByte
 move.b 0(a0,totalWidth),MaskByte
 
 ; ----------
 ; The MaskTable is saved compactly since none of the
 ; Masks are wider than one Byte.  We have to un-pack
 ; each Table entry so the high-order Bit of the
 ; totalWidth-bit-wide field is set:
 
.UnPack add.l  MaskByte,MaskByte
 bpl.s  .UnPack
 
 ; ----------
 ; Top Bit is now set.  Now, swing the top totalWidth
 ; Bits around to the bottom totalWidth Bits.  The
 ; first sequence element is now the Mask itself:
 
 rol.l  totalWidth,MaskByte
 move.l MaskByte,cyMaskByte
 
 ; ----------
 ; Do all sorts of preparation:
 
 move.l .srcOurs+.ourBase,temp; Setup base address:
 lsl.l  #3,temp  ;   Byte --> Bit address.
 move.l temp,srcAdr1Bit
 ; ----------
 move.w .srcOurs+.ourLbits,temp  ; Skip the Left margin.
 ext.l  temp
 add.l  temp,srcAdr1Bit
 ; ~~~~~~~~~~
 move.l .dstOurs+.ourBase,temp; Ditto for destination.
 lsl.l  #3,temp
 move.l temp,dstAdr1Bit
 ; ----------
 move.w .dstOurs+.ourLbits,temp
 ext.l  temp
 add.l  temp,dstAdr1Bit
 ; ~~~~~~~~~~
 move.w .srcOurs+.ourCols,pixWide
 move.w .srcOurs+.ourRows,temp; Normalized -->
 addq.w #1,temp  ;   un-Normalized.
 ext.l  temp
 lsl.l  widthSrc,temp
 move.l temp,a4
 move.w widthSrc,d2

 ; ----------
 ; Try to reduce the amount we shift down D2.  This 
 ; process involves halving the Strides as long as 
 ; each is even, decrementing D2 as we go & masking the
 ; the bottom bits off D4 when we extract the row count:
 
 move.w .srcOurs+.ourStride,d4
 move.w .dstOurs+.ourStride,d7
 move.w .srcOurs+.ourRows,d1
 tst.w  d2
 beq.s  .HalfDone
 
.HalfLoop btst #0,d4
 bne.s  .HalfDone
 btst #0,d7
 bne.s  .HalfDone
 lsl.w  #1,d1
 bcs.s  .HalfDone
 lsr.w  #1,d4
 lsr.w  #1,d7
 subq.w #1,d2
 bne.s  .HalfLoop
 
.HalfDone move.w d4,.srcOurs+.ourStride
 move.w d7,.dstOurs+.ourStride
 clr.l  d6
 
 ; ----------
 ; Make some stuff faster to access -- use the fact
 ; that (An) is faster to access than d(An):
 
 push.l srcAdr1Bit ; Exit MACRO destroys A0.
 clr.w  -(sp)    ; FUNCTIONal result.
 pea  .srcOurs+.ourStride ; VARs ...
 pea  .dstOurs+.ourStride
 bsr  MulChk
 tst.w  (sp)+
 beq  .Main
 
 ; ----------
.NoMul  pop.l  srcAdr1Bit
 push.l cyMaskByte
 move.w .srcOurs+.ourStride,srcLOGstride   ; Replaced by
 move.w .dstOurs+.ourStride,dstLOGstride   ;   their LOGs.
 
.MulLooptst.w  d2
 beq.s  .NoMul2
 cmpi.w #0,srcLOGstride
 beq.s  .NoMul2
 cmpi.w #0,dstLOGstride
 beq.s  .NoMul2
 ; ----------
 subq.w #1,d2
 subq.w #1,srcLOGstride
 subq.w #1,dstLOGstride
 bra.s  .MulLoop
 
.NoMul2 tst.w  d2
 bne.s  .Nloop
 cmpi.w #0,srcLOGstride
 bne.s  .Nloop
 cmpi.w #0,dstLOGstride
 bne.s  .Nloop
 cmp.w  pixWide,bitMask
 bne.s  .Nloop
 move.w srcAdr1Bit,d6
 andi.b #7,d6
 bne.s  .Nloop
 move.w dstAdr1Bit,d6
 andi.b #7,d6
 beq.s  .Screen
 
 ; ----------
 ; This loop is used when both source & destination
 ; BitMaps have Strides that are powers of 2:
 
.Nloop  move.w srcLOGstride,.srcOurs+.ourStride
 move.w dstLOGstride,.dstOurs+.ourStride
 pop.l  cyMaskByte
 
.Nloop2 cmp.l  a4,cyMaskByte
 bge.s  .Nnext
 
.NloopRow move.w cyMaskByte,d6
 and.w  bitMask,d6
 cmp.w  pixWide,d6
 bgt.s  .Nnext
 move.l cyMaskByte,d4
 sub.w  d6,d4
 lsr.l  d2,d4
 move.w .srcOurs+.ourStride,d7
 move.l d4,d1
 lsl.l  d7,d1
 add.l  d6,d1
 add.l  srcAdr1Bit,d1
 move.b d1,d7
 lsr.l  #3,d1
 move.l d1,a3
 not.b  d7
 ; ----------
 move.w .dstOurs+.ourStride,d1
 lsl.l  d1,d4
 add.l  d6,d4
 add.l  dstAdr1Bit,d4
 move.b d4,d6
 lsr.l  #3,d4
 not.b  d6
 btst d7,(a3)
 move.l d4,a3
 bne.s  .NsetON
 bclr d6,(a3)
 
.Nnext  lsr.l  #1,cyMaskByte
 bhi.s  .NloopRow
 eor.l  d3,cyMaskByte
 cmp.l  d3,cyMaskByte
 bne.s  .Nloop2
 bra  .Done
 
.NsetON bsetd6,(a3)
 lsr.l  #1,cyMaskByte
 bhi.s  .NloopRow
 eor.l  d3,cyMaskByte
 cmp.l  d3,cyMaskByte
 bne.s  .Nloop2
 bra  .Done
 
 ; ----------
 ; Super-special case that holds for the entire screen:

.Screen move.w srcLOGstride,.srcOurs+.ourStride
 move.w dstLOGstride,.dstOurs+.ourStride
 pop.l  cyMaskByte
 move.l srcAdr1Bit,d6
 lsr.l  #3,d6
 move.l d6,srcAdr1Byte
 move.l dstAdr1Bit,d6
 lsr.l  #3,d6
 move.l d6,dstAdr1Byte
 bra.s  .N2Loop
 
.N2Head eor.l  MaskByte,cyMaskByte
 
.N2Loop cmp.l  a4,cyMaskByte
 bge.s  .N2Next
 
.N2LoopRowmove.l cyMaskByte,d1
 lsr.l  #3,d1
 btst cyMaskByte,0(srcAdr1Byte,d1)
 bne.s  .N2setON
 bclr cyMaskByte,0(dstAdr1Byte,d1)
 
.N2Next lsr.l  #1,cyMaskByte
 bhi.s  .N2LoopRow
 bne.s  .N2Head
 bra.s  .N2Done
 
.N2setONbsetcyMaskByte,0(dstAdr1Byte,d1)
 lsr.l  #1,cyMaskByte
 bhi.s  .N2LoopRow
 bne.s  .N2Head
 
.N2Done move.w .srcOurs+.ourLbits,d0
 move.w .dstOurs+.ourLbits,d1
 bra  .DoneA; Alternate finish entry.
 
 ; ----------
 ; Main Loop:
 ;   Map the sequence element into rows & columns.
 ;   Check if it's in bounds and skip on if not.
 ;   Generate next element until finished.

.Main   pop.l  srcAdr1Bit
.MainLoop cmp.l  a4,cyMaskByte; Is row in bounds ??
 bge.s  .Next
 
 ; ----------
 ; Map it into the column.  Then check bounds:
 
.LoopRowmove.w cyMaskByte,d6
 and.w  bitMask,d6
 cmp.w  pixWide,d6
 bgt.s  .Next
 move.l cyMaskByte,d4
 sub.w  d6,d4
 lsr.l  d2,d4
 
 ; ----------
 ; Get the Source Byte & Bit offset:
 
 move.w .srcOurs+.ourStride,d1
 mulu d4,d1
 add.l  d6,d1
 add.l  srcAdr1Bit,d1
 move.b d1,d7
 lsr.l  #3,d1    ; --> Byte address.
 move.l d1,a3
 not.b  d7
 
 ; ----------
 ; Find Destination Bit address & Bit offset:
 
 move.w .dstOurs+.ourStride,d1
 mulu d1,d4
 add.l  d6,d4
 add.l  dstAdr1Bit,d4
 move.b d4,d6
 lsr.l  #3,d4    ; --> Byte address.
 not.b  d6
 btst d7,(a3)
 move.l d4,a3
 bne.s  .setON
 bclr d6,(a3)
 
 ; ----------
 ; Find next sequence element:
 
.Next   lsr.l  #1,cyMaskByte
 bhi.s  .LoopRow
 eor.l  MaskByte,cyMaskByte
 cmp.l  MaskByte,cyMaskByte
 bne.s  .MainLoop
 bra  .Done
 
.setON  bsetd6,(a3)
 lsr.l  #1,cyMaskByte
 bhi.s  .LoopRow
 eor.l  MaskByte,cyMaskByte
 cmp.l  MaskByte,cyMaskByte
 bne.s  .MainLoop
 
 ; ----------
 ; When we're finished:
 
.Done   move.w .srcOurs+.ourLbits,d0
 move.w .dstOurs+.ourLbits,d1
 not.b  d0
 not.b  d1
 
 ; Alternate finish entry:
 
.DoneA  move.l .srcOurs+.ourBase,a0
 move.l .dstOurs+.ourBase,a1
 bset d1,(a1)
 btst d0,(a0)
 bne.s  .end
 bclr d1,(a1)
 ; ----------
.end    ShowCursor ; It's show time, folks !!
 movem.l(sp)+,d1-d7/a0-a5 ; Withdraw all your savings.

 exit
 
 page
 
;****************************************************************
; FUNCTION  Convert (srcMap: BitMap; innerRect: Rect;
;     VAR ourRecord: Record): BOOLEAN;
; Convert a rectangle and an enclosing BitMap to our internal format:

Convert funcboolean; Successful ??
.srcMap long; --> enclosing BitMap or PixMap.
.innerRectpointer; Inner Rectangle.
.ourRecordvar    ; Our internal structure.
 endParms
 
 locals
.colorExistsboolean
.onScreen pointer
.pixelSizeinteger
.srcRowBytesinteger
 endLocals
 
 dsec 0 ; Our special Record.
.ourRowsword; Last row# and column# of inner
.ourColsword;   Rectangle [normalized to 0].
.ourLbits word   ; Ignored Bits in 1st Byte of Rect.
.ourStrideword   ; rowBits in bitMap.
.ourBasepointer  ; ... to 1st Byte in inner Rect.
 dend .ourSize
 
 
 enter
 
 movem.ld0-d2/a1-a5,-(sp) ; Your life preserver.
 clr.w  .result  ; Assume NOT okay !!
 
 ; ----------
 ; Color stuff:
 
.getMapInfo clr.w-(sp)    ; FUNCTIONal result.
 bsr  TestForColor
 pop.w  .colorExists
 
 tst.b  .colorExists
 beq.s  .blackWhite
 ; ----------
.color  GetCWMgrPort !.onScreen  ; The WHOLE thing !!
 move.l .onScreen,a0 ; A Pointer.
 move.l portPixMap(a0),a1 ; Handle -->
 move.l (a1),a1  ;   Pointer.
 move.w pmPixelSize(a1),.pixelSize
 bra.s  .setup
 ; ----------
.blackWhite move.w #1,.pixelSize

 ; ----------
 ; Setup Registers and zero-out our returned Record:
 
.setup  move.l .srcMap,a1
 move.w rowBytes(a1),.srcRowBytes
 andi.w #$3FFF,.srcRowBytes ; ... just for color.
 move.l .innerRect,a2
 move.l .ourRecord,a3
 move.l #.ourSize-1,d0
.clear  clr.b  (a3)+
 dbra d0,.clear
 move.l .ourRecord,a3; Reset to passed Pointer.
 
 ; ----------
 ; Now, fill-in our returned Record:
 ;
 ;   First, calculate address of the 1st Byte in 1st
 ;   row of BitMap occupied by the inner Rectangle.
 
 clr.l  d0
 clr.l  d1
 ;
 move.w top(a2),d0
 sub.w  bounds+top(a1),d0 ; How many rows down = dv.
 mulu .srcRowBytes,d0; Bytes down from (0,0).
 add.l  baseAddr(a1),d0
 ; ----------
 move.w left(a2),d1
 sub.w  bounds+left(a1),d1; Then, Bits across to Rect.
 mulu .pixelSize,d1
 ; ----------
 move.w d1,d2
 andi.w #7,d2    ; MOD 8.
 move.w d2,.ourLbits(a3)  ; # of Bits to skip.
 ; ----------
 lsr.w  #3,d1    ; Bytes across to Rectangle.
 add.l  d1,d0    ; Address of 1st Byte in Rect.
 move.l d0,.ourBase(a3)
 ; ----------
 move.w .srcRowBytes,d0
 lsl.w  #3,d0    ; Bytes --> Bits.
 move.w d0,.ourStride(a3)
 ; ----------
 move.w bottom(a2),d0
 sub.w  top(a2),d0 ; Height of Rectangle.
 subq.w #1,d0    ; Normalized to 0.
 bmi.s  .end; Zero height to begin with.
 move.w d0,.ourRows(a3)
 ; ----------
 move.w right(a2),d1
 sub.w  left(a2),d1; Width.
 mulu .pixelSize,d1
 subq.w #1,d1    ; Normalized to 0.
 bmi.s  .end; Zero width to begin with.
 move.w d1,.ourCols(a3)
 
 st.result; Everything's okay !!
 ; ----------
.end    movem.l  (sp)+,d0-d2/a1-a5 ; Withdraw all your savings.
 

 exit

 page
 
;****************************************************************
; FUNCTION  MulChk (VAR srcStride,dstStride: INTEGER): BOOLEAN;
; See if we can do without multiply instructions:

MulChk  funcboolean; Can we ??
.srcStridevar    ; Pointers.
.dstStridevar
 endParms
 
 noLocals
 
.strideWidthrequ d0
.one    requd1
.saveSrcWidth  requd2
 
 
 enter
 
 movem.ld0-d2/a1-a2,-(sp) ; Save your pennies.
 ; ----------
 clr.w  .result  ; Assume NO !!
 
 move.l .srcStride,a1
 move.w (a1),d0
 ext.l  d0
 subq.l #1,d0
 clr.w  -(sp)    ; FUNCTIONal result.
 push.l d0
 bsr  BitWidth
 pop.w  .strideWidth
 move.w #1,.one  ; Can we reproduce it ??
 lsl.w  .strideWidth,.one
 cmp.w  (a1),.one
 bne.s  .end; Nope, so bag it !!
 move.w .strideWidth,.saveSrcWidth
 ; ----------
 move.l .dstStride,a2
 move.w (a2),d0
 ext.l  d0
 subq.l #1,d0
 clr.w  -(sp)
 push.l d0
 bsr  BitWidth
 pop.w  .strideWidth
 move.w #1,.one
 lsl.w  .strideWidth,.one
 cmp.w  (a2),.one
 bne.s  .end; Bag it !!
 
 move.w .saveSrcWidth,(a1); ... source
 move.w .strideWidth,(a2) ; ... destination  
 st.result; Good News, folks !!
 ; ----------
.end    movem.l  (sp)+,d0-d2/a1-a2

 exit
 
 page
 
;****************************************************************
; FUNCTION  BitWidth (number: LONGINT): INTEGER;
; Find the number of Bits in a number:

BitWidthfuncinteger
.number longint
 endParms
 
 noLocals
 
 
 enter

 movem.ld0-d1,-(sp); Your life preserver.
 ; ----------
 clr.w  .result  ; Initialize to 0.
 move.l .number,d0
 beq.s  .end
 ; ----------
 move.w #32,d1   ; e.g., width of #3 = 2.
.loop   lsl.l  #1,d0
 dbcs d1,.loop   ; ... until a 1 falls off.
 move.w d1,.result
 ; ----------
.end    movem.l  (sp)+,d0-d1; To the rescue.
 
 exit
 
 page
 
;****************************************************************
; Table of longword Masks to XOR in Knuthian algorithm.  The first
; table entry > 0 is for a bit-width of two, so the table actually
; starts two bytes before that.  The scheme used is that of a 
; "maximum-length sequence generator":

MaskTable dc.b 0 ; Bit-width = 0 ...
 dc.b 0,3,3,3,5,3,3,23
 dc.b 17,9,5,101,27,53,3,45
 dc.b 9,129,57,9,5,3,33,27
 dc.b 9,113,57,9,5,101,9,163; ... Bit-width = 32.
 
 align

 page

; ======================================
; FUNCTION  TestForColor : BOOLEAN;
;
; Test for the presence of a Mac with Color QuickDraw AND a Color
; Monitor that the user has set to Color via the Control Panel:

TestForColorfunc boolean
 noParms
 
 locals
.theWorld byte sysEnv1Size; Mac II stuff.
 endLocals
 
 
 enter
 
 
 movem.ld1-d7/a0-a5,-(sp) ; Save all your pennies !!
 ; ==========
 
 clr.w  .result  ; Assume NO color = B&W.
 
 move.w #1,d0    ; Version #1.
 lea  .theWorld,a0
 _SysEnvirons
 tst.w  d0
 bne.s  .notColor
 ; ----------
.noErrortst.b  hasColorQD(a0) ; A0 --> theWorld.
 beq.s  .notColor
 ; ----------
 GetGDevice =a1  ; Handle -->
 move.l (a1),a1  ;   Pointer.
 move.l gdPMap(a1),a0; Ditto ...
 move.l (a0),a0
 cmpi.w #1,pmPixelSize(a0)
 beq.s  .notColor

.color  st.result
 ; ----------
.notColor

 ; ==========
.end    movem.l  (sp)+,d1-d7/a0-a5 ; Withdraw your life savings !!
 
 
 exit

Listing: Rotate.R

* "Rotate.R"
* -- the Resources for "Rotate"
*
* -- using "RMaker" { v 2.0 }


* /QUIT

RotateRSRC
????JALR

INCLUDE MonsterPICT
INCLUDE GigantorPICT
INCLUDE LogoPICT
INCLUDE MoofSND
INCLUDE oopsSND
INCLUDE ZoomSNDs



**********************************************************
* These are the Finder's "Get Info" strings:

TYPE vers = GNRL
topString,2
.H
0105    ;; version = 1 & revision = 5
8002    ;; revStage = 128 & buildNbr = 2
.I
0;; languageInt
.P
IACS    ;; abbrevStr
.P
\A91989   I\A5A\A5C\A5S Software ;; right below name

*--------*

TYPE vers = GNRL
bottomString,1
.H
0105
8002
.I
0
.P
1.\AF
.P
1.\AF ... in color too, folks !!

**********************************************************
* Other Finder-related resources.  These are responsible
* for displaying my unique ICON on the DeskTop:

TYPE JALR = GNRL ;; TYPE = Signature.
 ,0;; ID = 0, by convention.
.P
RotationDemo {v 1.\AF}

*--------*

TYPE BNDL
 ,128
JALR 0  ;; Signature & Resource ID.
ICN#    ;; Type 1.
0 128   ;; Local ID, Actual ID of the Icon.
FREF    ;; .. Type 2.
0 128   ;; .. Local ID, Actual ID of the Icon.
 
*--------*

TYPE FREF
 ,128
APPL 0  ;; File Type & Local ID of file's Icon.

*--------*

TYPE ICN# = GNRL ;; DeskTop Icon.
IACS,128
.H
*
********** Data **********
*
0000 0000 0000 0000 6040 FC7E 60E0 FC7E 61B0 C060 6318 C060 6318 C060 
6318 C060
6318 C060 6318 C060 6318 C060 6318 C060 63F8 C07E 63F8 C07E 6318 C006 
6318 C006
6318 C006 6318 C006 6318 C006 6318 C006 6318 C006 6318 C006 6318 C006 
6318 FC7E
6318 FC7E 0000 0000 0000 0000 0000 0000 7FFF FFFE 7FFF FFFE 0000 0000 
0000 0000
*
********** Mask **********
*
FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF 
FFFF FFFF
FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF 
FFFF FFFF
FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF 
FFFF FFFF
FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF FFFF 
FFFF FFFF

**********************************************************

TYPE MENU
 ,1001  ;; Resource ID.
\14;; Menu Title.
Rotation Demo ... Version 1.\AF
(-

 ,1002
Edit
Undo/Z  ;; Command Key.
(-
Cut/X
Copy/C
Paste/V
Clear

 ,1003
Graphic Effects
Rotate/R<B<O^9   ;; ...  + style(s) + ICON or cicn {ID = 265}.
Dissolve/D<I
(-
Quit/Q

*========*

TYPE mctb = GNRL
colorMenus,0;; Loaded by _InitMenus.
.H
0008    ;; # of MCEntries, including the last one.
*--------*
* MenuBar entry:
*--------*
0000    ;; mctID for the MenuBar.
0000    ;; mctItem for the MenuBar.
FFFF 0000 0000   ;; mctRGB1 = default color for title (red).
E000 E000 E000   ;; mctRGB2 = default color for background
*;;           of a pulled-down Menu (light gray).
0000 0000 FFFF   ;; mctRGB3 = default color for items (blue).
FC00 F37D 052F   ;; mctRGB4 = color of MenuBar (yellow).
0000    ;; mctReserved.
*--------*
* Different-from-normal title entry.  Otherwise,
* the MenuBar entry above takes care of it:
*--------*
03EB    ;; Graphic Effects Menu's ID.
0000    ;; Item #0 stands for its title.
0000 0000 FFFF   ;; Title's color (blue).
FC00 F37D 052F   ;; MenuBar's color (yellow).
0000 0000 FFFF   ;; Default color for Item(s) (blue).
E000 E000 E000   ;; Background color (light gray).
0000
*--------*
* Different-from-normal item entries.  Otherwise,
* the MenuBar entry above takes care of them:
*--------*
03E9    ;; Apple Menu's ID.
0002    ;; Item # of the dotted line separator.
0000 0000 0000   ;; Mark color (black).
0000 FFFF 0000   ;; Name color (green).
0000 0000 0000   ;; Command color (black).
E000 E000 E000   ;; Background color (light gray).
0000    ;; mctReserved.
*++++++++*
03EB    ;; Graphic Effects Menu's ID.
0001    ;; Item # for "Rotate".
0000 0000 0000
1D8B D8AB FFFF   ;; Name color = light blue.
FFFF 0000 0000   ;; Command color = red.
E000 E000 E000
0000
*++++++++*
03EB    ;; Graphic Effects Menu's ID.
0002    ;; Item # for "Dissolve".
0000 0000 0000
0000 FFFF 0000   ;; Name color = green.
FFFF 0000 0000
E000 E000 E000
0000
*++++++++*
03EB
0003    ;; Item # of the dotted line separator.
0000 0000 0000
0000 0000 FFFF   ;; Name color = blue.
FFFF 0000 0000
E000 E000 E000
0000
*++++++++*
03EB
0004    ;; Quit.
0000 0000 0000
0000 0000 0000   ;; Name color = black.
0000 FFFF 0000   ;; Command color = green.
E000 E000 E000
0000
*--------*
FF9D    ;; last entry marker (ID = -99) ...
0000 0000 0000 0000 0000 0000 0000 0000 0000 0000 0000 0000 0000 0000

**********************************************************

TYPE WIND
Main,128
Rotation Demo    ;; Title.
30 40 330 440    ;; picFrame := 0,0,272,274
Invisible GoAway
8;; zoomDocProc
0;; refCon

*--------*

TYPE wctb = GNRL
Main,128
.H
00000000;; wCSeed
0000    ;; wCReserved
0004    ;; # of entries - 1
*
* Text color = color of window's title.
* Hilite color = color of horizontal lines, close box and
*                grow box in title bar.
* Color of title bar = color around horizontal lines and
*                      the two boxes in the title bar.
*
0000 FFFF FFFF FFFF;; wContentColor  = white
0001 FFFF 0000 0000;; wFrameColor    = red
0002 0000 0000 FFFF;; wTextColor     = blue
0003 0000 0000 0000;; wHiliteColor   = black
0004 0000 FFFF 0000;; wTitleBarColor = green

*////////*

TYPE CNTL
horizontal,128
|;; Title for Control = none.
284 0 300 385    ;; 300-scrollHeight,0,300,400-growBoxSize
*;; < Resized by program. >
Invisible
16 ;; scrollBarProc
128;; User-defined value for refcon.
0 40 0  ;; min, max & initial value of Control.
*;; < maximum set by the program >

*--------*

TYPE cctb = GNRL
horizontal,128
.H
00000000;; ccSeed
0000    ;; ccReserved
0003    ;; # of entries - 1
*
* Frame color = also, the foreground/body color for highlighted Arrows.
* Body color = also, the shaft's color for a de-activated control.
* Text color = unused for a Scroll Bar.
* Thumb color = its fill color.
*
0000 FFFF 0000 0000;; cFrameColor  = red
0001 FFFF FFFF FFFF;; cBodyColor  = white
0002 0000 0000 0000;; cTextColor  = black
0003 0000 0000 FFFF;; cThumbColor  = blue

*////////*

TYPE CNTL
vertical,129
|
0 384 285 400    ;; 0,400-scrollWidth,300-growBoxSize,400
Invisible
16
129
0 30 0

*--------*

TYPE cctb = GNRL
vertical,129
.H
00000000;; ccSeed
0000    ;; ccReserved
0003    ;; # of entries - 1
*
0000 FFFF 0000 0000;; cFrameColor  = red
0001 FFFF FFFF FFFF;; cBodyColor  = white
0002 0000 0000 0000;; cTextColor  = black
0003 0000 0000 FFFF;; cThumbColor  = blue

**********************************************************

TYPE WIND
Brag,129
Brag a Little
60 40 285 480    ;; picFrame = (54,126,251,540)
Invisible NoGoAway
3;; altDBoxProc
0

**********************************************************

TYPE acur = GNRL
RotatingEarth,128 (20)    ;; Preloaded + Locked.
.H
0007    ;; # of CURSors in list.
0000    ;; Used as a frame counter.
00800000;; CURSor IDs in High word ...
00810000
00820000
00830000
00840000
00850000
00860000;; End of list

*========*

TYPE CURS = GNRL
Earth1,128 (20)
.H
07C0 19B0 2C98 763C 7D3C BB12 BE0E BE1E;; Data (16 X 16)
9D1E 8C0E 4784 4784 2308 1B30 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE;; Mask (16 X 16)
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000;; Hot Spot (point)

*--------*

TYPE CURS = GNRL
Earth2,129 (20)
.H
07C0 1F30 2D98 4ECC 4FA4 8762 87C2 87C2
83A2 8182 40F4 40F4 2068 1870 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

*--------*

TYPE CURS = GNRL
Earth3,130 (20)
.H
07C0 1870 30E8 70F4 50F4 E07E E07E C07A
803A C81A 5C0C 7C04 2008 1830 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

*--------*

TYPE CURS = GNRL
Earth4,131 (20)
.H
07C0 19B0 3F18 7F0C FD0C FE02 FE02 FC02
A802 8482 51C4 43C4 2008 1C30 07C0 0000
*
07C0 1FF0 3FF8 7FFC FFFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

*--------*

TYPE CURS = GNRL
Earth5,132 (20)
.H
07C0 1C70 3FD8 7FFC 7FD4 9FE2 EFE2 F6C2
F282 E04A 611C 503C 2008 1830 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

*--------*

TYPE CURS = GNRL
Earth6,133 (20)
.H
07C0 1F30 3FF8 7FFC 7FFE 91FE 8EFE 9F6E
9F2A 8E02 4E14 4D04 2008 1830 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

*--------*

TYPE CURS = GNRL
Earth7,134 (20)
.H
07C0 1AB0 29F8 63FC 53FC B11E E0CE E1F2
D1F2 C0E2 78E4 78D4 3008 1830 07C0 0000
*
07C0 1FF0 3FF8 7FFC 7FFC FFFE FFFE FFFE
FFFE FFFE 7FFC 7FFC 3FF8 1FF0 07C0 0000
*
00000000

**********************************************************

TYPE acur = GNRL
DogCow,129 (20)
.H
0008
0000
00900000
00910000
00920000
00930000
00940000
00950000
00960000
00970000

*========*

TYPE CURS = GNRL
DogCow1,144 (20)
.H
0000 0000 0000 1600 3E01 5403 C305 F3FD
08FA 0C72 0C02 0DF2 0A0A 0A0A 0A0A 1C1E
*
0000 0000 0000 1600 3E01 7C03 FF07 FFFF
0FFE 0FFE 0FFE 0FFE 0E0E 0E0E 0E0E 1C1E
*
00060000

*--------*

TYPE CURS = GNRL
DogCow2,145 (20)
.H
0000 FF80 4B00 E3C0 1180 09C0 0CE0 1CF0
207F 2C02 2A3C 4920 30A0 0090 0050 0060
*
0000 FF80 7F00 FFC0 1F80 0FC0 0FE0 1FF0
3FFF 3FFE 3BFC 79E0 30E0 00F0 0070 0060
*
00060000

*--------*

TYPE CURS = GNRL
DogCow3,146 (20)
.H
3030 2838 2424 13AC 0BC6 040C 0236 0236
02E0 02E0 0EE0 1060 2620 2990 2850 3038
*
3030 3838 3C3C 1FBC 0FFE 07FC 03F6 03F6
03E0 03E0 0FE0 1FE0 3FE0 39F0 3870 3038
*
00060000

*--------*

TYPE CURS = GNRL
DogCow4,147 (20)
.H
000A 080E 170A 1092 0EE6 02C2 040E 083E
30FA C1E8 9DC0 6580 0500 0500 0300 0100
*
000A 080E 1F0E 1F9E 0FFE 03FE 07FE 0FFE
3FFA FFE8 FFC0 6780 0700 0700 0300 0100
*
00060000

*--------*

TYPE CURS = GNRL
DogCow5,148 (20)
.H
0000 06C0 0AA0 1290 1458 17D8 2018 2718
4F18 9FCF E0C3 802A 00FC 00D0 0000 0000
*
0000 06C0 0EE0 1EF0 1C78 1FF8 3FF8 3FF8
7FF8 FFFF E0FF 803E 00FC 00D0 0000 0000
*
00060000

*--------*

TYPE CURS = GNRL
DogCow6,149 (20)
.H
0600 0A00 0900 050C 0492 3C54 4034 FE04
0F38 0730 0390 0188 03C7 00D2 01FF 0000
*
0600 0E00 0F00 070C 079E 3FDC 7FFC FFFC
0FF8 07F0 03F0 01F8 03FF 00FE 01FF 0000
*
00060000

*--------*

TYPE CURS = GNRL
DogCow7,150 (20)
.H
0E06 050A 04CA 0232 0304 03B8 03A0 03A0
3620 3620 1810 31E8 1AE4 1212 0E0A 0606
*
0E06 070E 07CE 03FE 03FC 03F8 03E0 03E0
37E0 37E0 1FF0 3FF8 1EFC 1E1E 0E0E 0606
*
00060000

*--------*

TYPE CURS = GNRL
DogCow8,151 (20)
.H
0080 00C0 00A0 00A0 01A6 03B9 0F83 3F8C
7C10 7020 4340 6770 4908 50E8 7010 5000
*
0080 00C0 00E0 00E0 01E6 03FF 0FFF 3FFC
7FF0 7FE0 7FC0 7FF0 79F8 70F8 7010 5000
*
00060000

**********************************************************

TYPE pltt = GNRL
Main,128
.H
*
* # of pmEntries ( 6 words + 1 long, each ):
*
000A
*
* pmDataFields used by the Palette Manager:
*
0000 0000 0000 0000 0000 0000 0000
*
* pmInfoStart:
*
FFFF FFFF FFFF   ;; rgbWhite
0002    ;; ciUsage = pmTolerant
5000    ;; ciTolerance
0000    ;; ciFlags
00000000;; ciPrivate
* -----
0000 0000 0000   ;; rgbBlack
0002 5000 0000 00000000
* -----
FC00 F37D 052F   ;; rgbYellow
0002 5000 0000 00000000
* -----
F2D7 0856 84EC   ;; rgbMagenta
0002 5000 0000 00000000
* -----
DD6B 08C2 06A2   ;; rgbRed
0002 5000 0000 00000000
* -----
0241 AB54 EAFF   ;; rgbCyan
0002 5000 0000 00000000
* -----
0000 8000 11B0   ;; rgbGreen
0002 5000 0000 00000000
* -----
0000 0000 D400   ;; rgbBlue
0002 5000 0000 00000000
* -----
1D8B D8AB FFFF   ;; rgbLtBlue
0002 5000 0000 00000000
* -----
E000 E000 E000   ;; rgbLtGray
0002 5000 0000 00000000

**********************************************************

TYPE cicn = GNRL ;; Application's Icon.
IACS,128
*
********** IconPMap **********
*
.H
00000000;; pBaseAddr
8010    ;; pRowBytes = $8000 + pixelSize * rowBytes(4)
.I
0 0 32 32 ;; bounds
.H
0000    ;; pmVersion
0000    ;; packType
00000000;; packSize
00480000;; hRes
00480000;; vRes
0000    ;; pixelType
0004    ;; pixelSize
0001    ;; cmpCount
0004    ;; cmpSize = pixelSize
00000000;; planeBytes
00000000;; pmTable
00000000;; pmReserved
*
********** IconMask **********
*
00000000;; mBaseAddr
0004    ;; mRowBytes
.I
0 0 32 32 ;; bounds
*
********** IconBMap **********
*
.H
00000000;; 1BaseAddr
0004    ;; 1RowBytes
.I
0 0 32 32 ;; bounds
*
********** IconData **********
*
.H
00000000;; Placeholder for Handle.
*
********** MaskData **********
*
FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF
FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF
FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF
FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF FFFFFFFF
*
********** BMapData **********
*
00000000 00000000 6040FC7E 60E0FC7E 61B0C060 6318C060 6318C060 6318C060
6318C060 6318C060 6318C060 6318C060 63F8C07E 63F8C07E 6318C006 6318C006
6318C006 6318C006 6318C006 6318C006 6318C006 6318C006 6318C006 6318FC7E
6318FC7E 00000000 00000000 00000000 7FFFFFFE 7FFFFFFE 00000000 00000000
*
********** PMapCTab **********
*
00000000;; ictSeed
0000    ;; ictFlags
0007    ;; ictSize = (endICT-startICT)/8-1
*
********** startICT **********
*
0000 FFFF FFFF FFFF;; white
0001 FC00 F37D 052F;; yellow
0002 F2D7 0856 84EC;; magenta
0003 DD6B 08C2 06A2;; red
0004 0241 AB54 EAFF;; cyan
0005 0000 8000 11B0;; green
0006 0000 0000 D400;; blue
0007 0000 0000 0000;; black
*
********** endICT **********
*
********** PMapData **********
*
77777777 77777777 77777777 77777777
77777777 77777777 77777777 77777777
70077777 70777777 00000077 70000007
70077777 00077777 00000077 70000007
70077770 07007777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 77700777 00777777 70077777
70077700 00000777 00777777 70000007
70077700 00000777 00777777 70000007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00777777 77777007
70077700 77700777 00000077 70000007
70077700 77700777 00000077 70000007
77777777 77777777 77777777 77777777
77777777 77777777 77777777 77777777
77777777 77777777 77777777 77777777
70000000 00000000 00000000 00000007
70000000 00000000 00000000 00000007
77777777 77777777 77777777 77777777
77777777 77777777 77777777 77777777

**********************************************************

TYPE cicn = GNRL ;; Ugly, ain't he ?!*!?
FaceIcon,265;; ... for Rotate Menu Item.
*
********** IconPMap **********
*
.H
00000000
8010
.I
0 0 32 32
.H
0000
0000
00000000
00480000
00480000
0000
0004
0001
0004
00000000
00000000
00000000
*
********** IconMask **********
*
00000000
0004
.I
0 0 32 32
*
********** IconBMap **********
*
.H
00000000
0004
.I
0 0 32 32
*
********** IconData **********
*
.H
00000000
*
********** MaskData **********
*
00BFEF80 01BFBFC0 03FFFFE0 0EFFFFF0 07FFFFF8 0FFFFFF0 0FFFFFF8 1FFFFFF8
0FFFFFFC 3FFFFFFE 3FFFFFFE 1FFFFFFE 7FFFFFFE 3FFFFFFC 7FFFFFFE 3FFFFFFE
7FFFFFFE 1FFFFFFE 0FFFFFFE 1FFFFFFE 0FFFFFFF 07FFFFF8 01FFFFF0 00FFFFC0
00FFFEC0 00FFFFF8 01FFFFFF 03FFFFFF 1FFFFFFE 7FFFFFE0 FFFFFFC0 01FFFF00
*
********** BMapData **********
*
0017C300 00BFAF80 01B7FFC0 06EFB7E0 03F73AF0 07D40960 05C20330 0FA00230
07800138 1D8001FC 178000DC 0F8000FC 3FBA2F6C 1BBDDC88 3B566A4C 190A1D4C
3C024054 0C8640BC 07742E3C 0F034034 058FF87A 029BECD0 009C1CA0 0043E080
0061C280 00400070 0050044E 00C80861 0783E060 18800040 20C000C0 00600300
*
********** PMapCTab **********
*
00000000
0000
0006
*
********** startICT **********
*
0000 FFFF FFFF FFFF;; white
0001 FFFF B95B AD15;; light flesh
0002 FFFF 8978 70E4;; dark flesh
0003 DD6B 08C2 06A2;; red
0004 7EFF 41F2 22FD;; brown
0005 0000 0000 D400;; blue
0006 0000 0000 0000;; black
*
********** endICT **********
*
********** PMapData **********
*
00000000 00060666 66000066 00000000
00000000 60666666 60606666 60000000
00000006 60660666 66666666 66000000
00000660 66616666 61661666 66600000
00000066 66661666 11666161 66660000
00000666 66161611 11116116 16600000
00000606 66111161 11111166 11660000
00006666 61611111 11111161 11660000
00000666 61111111 11111116 11666000
00066606 61111111 11111116 66666600
00060666 61111111 11111111 66166600
00006666 61111111 11111111 66666600
00666666 33333131 13333331 16616600
00066163 41444313 34144413 61116000
00666163 14141321 34414143 16116600
00066113 11114321 31144413 16116600
00666613 11111321 31111113 16160600
00006611 33333121 13333331 61666600
00000666 11111211 11111111 11666600
00006666 11111122 12111111 11660600
00000606 11112222 22222111 16666060
00000060 11122122 22212211 66060000
00000000 11122211 11122211 10600000
00000000 01111122 22211111 10000000
00000000 01111112 22111121 10000000
00000000 02111111 11111211 55550000
00000000 51121111 11112111 55555550
00000005 51112111 11121111 55555550
00005555 11111222 22111111 55555500
00555555 55555555 55555555 55000000
05555555 55555555 55555555 50000000
00000000 55555555 55555550 00000000

**********************************************************
* Mac SE-&-below-version for the above:

TYPE ICON = GNRL
bwFaceIcon,265
.H
0017C300 00BFAF80 01B7FFC0 06EFB7E0 03F73AF0 07D40960 05C20330 0FA00230
07800138 1D8001FC 178000DC 0F8000FC 3FBA2F6C 1BBDDC88 3B566A4C 190A1D4C
3C024054 0C8640BC 07742E3C 0F034034 058FF87A 029BECD0 009C1CA0 0043E080
0061C280 00400070 0050044E 00C80861 0783E060 18800040 20C000C0 00600300

**********************************************************

TYPE crsr = GNRL ;; Put 'er there, Pardner!!
Hand,129
*
.H
8001    ;; crsrType
0000 0060 ;; offset to CrsrPMap
0000 0092 ;; offset to PMapData
0000 0000 ;; crsrXData
0000    ;; crsrXValid
0000 0000 ;; crsrXHandle
*
0380    ;; crsr1Data
04C0
04C0
04C0
04C0
04C0
74F8
9CAE
4CAB
240B
2403
1003
0803
0806
0406
0406
*
0380    ;; crsrMask
07C0
07C0
07C0
07C0
07C0
77F8
FFFE
7FFF
3FFF
3FFF
1FFF
0FFF
0FFE
07FE
07FE
*
0000 0007 ;; crsrHotSpot
0000 0000 ;; crsrXTable
0000 0000 ;; crsrID
*
* CrsrPMap
*
0000 0000 ;; pBaseAddr
8008    ;; pRowBytes
0000 0000 0010 0010;; pBounds
0000    ;; pmVersion
0000    ;; packType
0000 0000 ;; packSize
00480000;; hRes
00480000;; vRes
0000    ;; pixelType
0004    ;; pixelSize
0001    ;; cmpCount
0004    ;; cmpSize
0000 0000 ;; planeBytes
0000 0112 ;; offset to PMapCTab
0000 0000 ;; pmReserved
*
* PMapData
*
00000066 60000000
00000611 66000000
00000611 66000000
00000611 66000000
00000611 66000000
00000611 66000000
06660611 66666000
61166611 61616660
06116611 61616166
00611611 11116166
00611611 11111166
00061111 11111166
00006111 11111166
00006111 11111660
00000611 11111660
00000611 11111660
*
* PMapCTab
*
0000 0000 ;; ictSeed
0000    ;; ictFlags
0007    ;; ictSize = (endICT-startICT)/8-1
*
********** startICT **********
*
0000 FFFF FFFF FFFF;; white
0001 FC00 F37D 052F;; yellow
0002 F2D7 0856 84EC;; magenta
0003 DD6B 08C2 06A2;; red
0004 0241 AB54 EAFF;; cyan
0005 0000 8000 11B0;; green
0006 0000 0000 D400;; blue
0007 0000 0000 0000;; black
*
********** endICT **********

**********************************************************

TYPE ppat = GNRL ;; Pattern seen when dragging/growing a window.
Drag,128
*
********** PixPat record **********
*
.H
0002    ;; patType = RGB color pattern.
0000001C;; offset to pixMap record.
0000004E;; offset to pixel data.
00000000;; patXData
FFFF    ;; patXValid
00000000;; patXMap
AA ;; pat1Data
55
AA
55
AA
55
AA
55
*
********** PixMap record **********
*
00000000;; pBaseAddr
8008    ;; pRowBytes = $8000 + pixelSize * rowBytes(2)
.I
0 0 8 8 ;; bounds
.H
0000    ;; pmVersion
0000    ;; packType
00000000;; packSize
00480000;; hRes
00480000;; vRes
0000    ;; pixelType = chunky
0004    ;; pixelSize
0001    ;; cmpCount
0004    ;; cmpSize = pixelSize
00000000;; planeBytes
0000006E;; pmTable offset
00000000;; pmReserved
*
********** Pixel Data **********
*
10101010;; Color(s) recomputed by _MakeRGBPat
01010101;;   to approximate passed RGB.
10101010
01010101
10101010
01010101
10101010
01010101
*
********** PMapCTab **********
*
00000000;; pctSeed
0000    ;; pctFlags
0004    ;; pctSize = (endPCT-startPCT)/8-1
*
********** startPCT **********
*
0000 FFFF FFFF FFFF;; white   ( 1st 4 are computed )
0001 0000 0000 D400;; blue
0002 F2D7 0856 84EC;; magenta
0003 0000 0000 0000;; black
0004 0000 8000 11B0;; green   ( Passed color )
*
********** endPCT **********

**********************************************************

TYPE SIZE = GNRL
Rotate,-1
.H
* Flags word: Bit #15 = reserved { Save screen <Switcher> }
*                 #14 = acceptSuspendResumeEvents
*                 #13 = reserved { Disable option <Switcher> }
*                 #12 = canBackground
*                 #11 = multiFinderAware
*                 #10 = onlyBackground
*                 # 9 = getFrontClicks { do NOT set for CMD-dragging 
}
*                 # 8 = reserved { Accept "child-died" Events <debuggers> 
}
*                 # 7 = reserved { 32-bit compatible }
*                 # 6 -> 0 = reserved
5800
* next = LONGINT = preferred size
00060000                                ;; 384K { what uniFinder does 
WITHOUT MF !! }
* next = LONGINT = minimum size
00038000                                ;; 224K { left over from "Switcher" 
}

BLANK LINE AT END OF SOURCE

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Latest Forum Discussions

See All

Whitethorn Games combines two completely...
If you have ever gone fishing then you know that it is a lesson in patience, sitting around waiting for a bite that may never come. Well, that's because you have been doing it wrong, since as Whitehorn Games now demonstrates in new release Skate... | Read more »
Call of Duty Warzone is a Waiting Simula...
It's always fun when a splashy multiplayer game comes to mobile because they are few and far between, so I was excited to see the notification about Call of Duty: Warzone Mobile (finally) launching last week and wanted to try it out. As someone who... | Read more »
Albion Online introduces some massive ne...
Sandbox Interactive has announced an upcoming update to its flagship MMORPG Albion Online, containing massive updates to its existing guild Vs guild systems. Someone clearly rewatched the Helms Deep battle in Lord of the Rings and spent the next... | Read more »
Chucklefish announces launch date of the...
Chucklefish, the indie London-based team we probably all know from developing Terraria or their stint publishing Stardew Valley, has revealed the mobile release date for roguelike deck-builder Wildfrost. Developed by Gaziter and Deadpan Games, the... | Read more »
Netmarble opens pre-registration for act...
It has been close to three years since Netmarble announced they would be adapting the smash series Solo Leveling into a video game, and at last, they have announced the opening of pre-orders for Solo Leveling: Arise. [Read more] | Read more »
PUBG Mobile celebrates sixth anniversary...
For the past six years, PUBG Mobile has been one of the most popular shooters you can play in the palm of your hand, and Krafton is celebrating this milestone and many years of ups by teaming up with hit music man JVKE to create a special song for... | Read more »
ASTRA: Knights of Veda refuse to pump th...
In perhaps the most recent example of being incredibly eager, ASTRA: Knights of Veda has dropped its second collaboration with South Korean boyband Seventeen, named so as it consists of exactly thirteen members and a video collaboration with Lee... | Read more »
Collect all your cats and caterpillars a...
If you are growing tired of trying to build a town with your phone by using it as a tiny, ineffectual shover then fear no longer, as Independent Arts Software has announced the upcoming release of Construction Simulator 4, from the critically... | Read more »
Backbone complete its lineup of 2nd Gene...
With all the ports of big AAA games that have been coming to mobile, it is becoming more convenient than ever to own a good controller, and to help with this Backbone has announced the completion of their 2nd generation product lineup with their... | Read more »
Zenless Zone Zero opens entries for its...
miHoYo, aka HoYoverse, has become such a big name in mobile gaming that it's hard to believe that arguably their flagship title, Genshin Impact, is only three and a half years old. Now, they continue the road to the next title in their world, with... | Read more »

Price Scanner via MacPrices.net

B&H has Apple’s 13-inch M2 MacBook Airs o...
B&H Photo has 13″ MacBook Airs with M2 CPUs and 256GB of storage in stock and on sale for up to $150 off Apple’s new MSRP, starting at only $849. Free 1-2 day delivery is available to most US... Read more
M2 Mac minis on sale for $100-$200 off MSRP,...
B&H Photo has Apple’s M2-powered Mac minis back in stock and on sale today for $100-$200 off MSRP. Free 1-2 day shipping is available for most US addresses: – Mac mini M2/256GB SSD: $499, save $... Read more
Mac Studios with M2 Max and M2 Ultra CPUs on...
B&H Photo has standard-configuration Mac Studios with Apple’s M2 Max & Ultra CPUs in stock today and on Easter sale for $200 off MSRP. Their prices are the lowest available for these models... Read more
Deal Alert! B&H Photo has Apple’s 14-inch...
B&H Photo has new Gray and Black 14″ M3, M3 Pro, and M3 Max MacBook Pros on sale for $200-$300 off MSRP, starting at only $1399. B&H offers free 1-2 day delivery to most US addresses: – 14″ 8... Read more
Department Of Justice Sets Sights On Apple In...
NEWS – The ball has finally dropped on the big Apple. The ball (metaphorically speaking) — an antitrust lawsuit filed in the U.S. on March 21 by the Department of Justice (DOJ) — came down following... Read more
New 13-inch M3 MacBook Air on sale for $999,...
Amazon has Apple’s new 13″ M3 MacBook Air on sale for $100 off MSRP for the first time, now just $999 shipped. Shipping is free: – 13″ MacBook Air (8GB RAM/256GB SSD/Space Gray): $999 $100 off MSRP... Read more
Amazon has Apple’s 9th-generation WiFi iPads...
Amazon has Apple’s 9th generation 10.2″ WiFi iPads on sale for $80-$100 off MSRP, starting only $249. Their prices are the lowest available for new iPads anywhere: – 10″ 64GB WiFi iPad (Space Gray or... Read more
Discounted 14-inch M3 MacBook Pros with 16GB...
Apple retailer Expercom has 14″ MacBook Pros with M3 CPUs and 16GB of standard memory discounted by up to $120 off Apple’s MSRP: – 14″ M3 MacBook Pro (16GB RAM/256GB SSD): $1691.06 $108 off MSRP – 14... Read more
Clearance 15-inch M2 MacBook Airs on sale for...
B&H Photo has Apple’s 15″ MacBook Airs with M2 CPUs (8GB RAM/256GB SSD) in stock today and on clearance sale for $999 in all four colors. Free 1-2 delivery is available to most US addresses.... Read more
Clearance 13-inch M1 MacBook Airs drop to onl...
B&H has Apple’s base 13″ M1 MacBook Air (Space Gray, Silver, & Gold) in stock and on clearance sale today for $300 off MSRP, only $699. Free 1-2 day shipping is available to most addresses in... Read more

Jobs Board

Medical Assistant - Surgical Oncology- *Apple...
Medical Assistant - Surgical Oncology- Apple Hill Location: WellSpan Medical Group, York, PA Schedule: Full Time Sign-On Bonus Eligible Remote/Hybrid Regular Apply Read more
Omnichannel Associate - *Apple* Blossom Mal...
Omnichannel Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Cashier - *Apple* Blossom Mall - JCPenney (...
Cashier - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Blossom Mall Read more
Operations Associate - *Apple* Blossom Mall...
Operations Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Business Analyst | *Apple* Pay - Banco Popu...
Business Analyst | Apple PayApply now " Apply now + Apply Now + Start applying with LinkedIn Start + Please wait Date:Mar 19, 2024 Location: San Juan-Cupey, PR Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.