TweetFollow Us on Twitter

Devices
Volume Number:4
Issue Number:3
Column Tag:Macintosh II

Graphics Devices & Chroma

By Greg Marriott, The MacHax™ Group

The Good(?) Old Days

How many of you Mac programmers out there remember how hard it was to master Quickdraw? Come on, raise your hands... Now, how many of you still have trouble sometimes? (Yes, my hand is up, too!) Remember those long hours spent trying to figure out how SetOrigin works, and wondering which regions stick to the window and which ones stick to the GrafPort coordinates? Wasn’t it a bummer trying to remember why FrameRgn and FramePoly produce different results? I can see you grimacing as you recall the many hours spent wondering where your pictures go when you offset them. I, for one, refused to knuckle under, and finally managed to get most of it figured out. From the abundance of Mac software out there, it looks like a lot of other people persevered as well.

Apple Consults Ted Turner (or Color, Anyone?)

Just when we had everything under control, along came Color Quickdraw! With it came several new concepts to absorb. The most obvious addition to the Mac’s graphics system is, of course, color. Obvious, that is, to all those lucky enough to have a color monitor attached. People with monochrome screens have to settle for lots of shades of gray. Really lucky people can have monochrome screens and color screens hooked up at the same time! This is where I (very smoothly) slide into a discussion of another addition to the Quickdraw system: the ability to have several display devices instead of a lone monitor. The phrase “display device” could apply to a wide variety of equipment, but I’ll limit my discussion to the CRTs we’ve come to know and love. (For a description of how the color part of Color Quickdraw works, read Inside Macintosh Vol. 5, and take a look at Steven Sheets’ article in the September ’87 MacTutor).

Six of One, Half a Dozen of the Other

As most of you know, the Mac II has expansion slots (for you trivia buffs out there, it has six of them). Each of these slots can have something really neat plugged into it, like additional processors, data acquisition boards, and other stuff like that. But, if you don’t have a video card and monitor plugged in, you won’t be able to see what’s going on. I ought to know. My monitor took about a month longer to arrive than my CPU did. The Mac made a nice sound when I turned it on, but that got really boring after the first couple of hundred times. Anyway, with six slots available, enterprising (and loaded) people can plug in six video cards to use with many monitors of various shapes and sizes (some cards allow more than one monitor to be attached).

So, with lots of screens putting quite a load on your table (not to mention your budget), what would you expect to see? Several identical copies of your desktop? Sounds interesting, but not very practical. Quickdraw treats all the video devices collectively as a single, possibly irregular, display. Windows may be placed anywhere on the desktop, and as a result a single window can extend across several monitors. The effect is especially impressive when adjacent monitors have different color environments, or one is color and the other b/w. This spectacular feat is accomplished through careful management of graphics devices.

Graphics Devices can be (loosely) described as anything Color Quickdraw can draw into (I’ll refer to Color QuickDraw as CQD from here on out). By the way, when I mention a graphics device I’m not talking about the piece of expensive hardware sitting on your desk. I’m referring to the data structure CQD uses to describe the piece of expensive hardware. A GDevice record holds information about the device’s postition in Quickdraw space, the color capabilities, color matching routines, and cursor handling on the device. Physical devices also have drivers associated with them, identified by the gdRefNum field, to handle things like changing the depth or color environment. For multiple screens, CQD maintains a linked list of GDevices (actually, it’s a list of handles to GDevices), one for each monitor. The head of the list is in a low memory global called DeviceList. The screen with the menu bar is described by the GDevice in MainDevice, also in low memory. When drawing is happening on a device, a handle to it is stored in theGDevice.

Normally, applications should ignore the fact that their windows might extend over more than one screen and let Quickdraw take care of the details. As a matter of fact, programs should never (well, almost never) depend on any particular device configuration, such as the number of colors present. The user can change the environment any time he wants to, one way being through the Control Panel.

Sometimes, though, taking advantage of the way graphics devices work can be useful. I’ve written a desk accessory to help illustrate some points to keep in mind when dealing with graphics devices. I’m not going to go over everything you should know about graphics devices here, since Inside Macintosh, Vol. 5 covers them very well.

What a Great Name For a Color DA!

Chroma is a desk accessory that displays all the colors (or gray shades) currently available on attached graphics devices. It pays attention to the depth (bits per pixel) of each device when deciding how many colors to draw. Other useful data are also displayed, such as the slot number a device is plugged into, the refNum of the driver, the GDevice flags, and the device’s mode. The flags indicate the presence of several conditions, including whether or not the device is the main screen, was initialized from RAM, was initialized from a ‘scrn’ resource, is the active screen, has a driver, and is color or b/w. The mode is the number passed to the driver, if there is one, to set the pixel depth, etc.

When the Chroma window lays across more than one device, the piece of the window on a device reflects that device’s environment. That is, a color monitor with 256 colors and a b/w monitor with 16 gray shades would cause Chroma to draw part of the window with lots of little color squares and the other part of the window with big gray ones. The rest of the information provided is also pertinent to the device on which it is drawn. By positioning the slot number on the boundary between screens, you’ll see part of a different number on each screen. Chroma starts with a rather small window, so you can leave it around to examine your color environment and not cover up other areas of interest. It supports zooming, though, so you can get a better look at the colors of a device. Chroma’s window zooms to fill the screen where the zoom box was when you hit it. (To learn about DA programming in general, see some past issues of MacTutor [Ed, how about suggesting some articles here?]).

A Self-Aware(!) Machine

Since Chroma’s activities take place in (potentially) color environments, it needs a color window. But, color windows can only be created in the presence of CQD. So, the first thing Chroma does when it’s opened is to make sure CQD is present. Some programs check this by looking at a low-memory global called ROM85 and seeing if they are on a Mac II. It’s true that CQD only runs on a Mac II, but that may not always be the case (we might see a color MacSE, but then again, that’s just a silly rumor... right?). A much more portable way to detect CQD is by calling SysEnvirons. The SysEnvirons call fills in a record describing the computer’s configuration. SysEnvirons notes the presence of CQD, a floating-point coprocessor, and the system version, among other things. For a detailed explanation of SysEnvirons, see Apple TechNote #129.

If Chroma is opened on a machine without CQD, it puts up a “regular” window instead of a color window, and draws a picture complaining about the lack of color tables to display. Notice that the b/w window is not allowed to zoom. It seems pretty silly to zoom an error message to fill the screen! Chroma keeps a boolean in its storage handle to indicate the presence (or absence) of CQD, so the window updating mechanism knows whether it can use color drawing commands or not.

How Things Work

Now I come to the “guts” of Chroma, its drawing procedures. Chroma draws the contents of its window whenever it receives an update event from the Desk Manager (or from itself, as explained later). The procedure to draw the contents is named, strangely enough, DrawWindow. It is called once for each device the Chroma window intersects. It’s easy to check for intersections, since part of a GDevice is the rectangle, in global coordinates, which describes the device’s position in Quickdraw space. If the content region of the Chroma window intersects any part of the device, the clip region for the window is set to the intersection and DrawWindow is called.

DrawWindow uses the Palette Manager (PM) to handle its color selections for the various devices. When the color window is created, Chroma makes a palette for it using NewPalette and installs it using SetPalette. Before drawing on each device, DrawWindow copies the color table from it into the palette using CTab2Palette. This call resizes the palette, if necessary, to have the same number of entries as the color table. A changed palette isn’t really useful until it’s activated, so ActivatePalette is called. When ActivatePalette is called with the frontmost window as a parameter, the PM attempts to provide a color environment containing as many colors in the palette as it can. To do this, the PM checks the color tables of each device the window intersects. It changes the color tables to achieve a best fit. But, Chroma isn’t designed to change color environments, just to show what’s already there. Lucky for us, the PM defines a special kind of palette entry that causes no change in the color environment. These “explicit” colors can be specified in our palette by passing pmExplicit in the srcUsage parameter of CTab2Palette. (Personal note about the PM: I thought it would be hard to get into the spirit of using the PM, but it’s not. Everybody writing color programs should use the PM. Using the PM will help to ensure compatibility with MultiFinder, a wide variety of graphics devices, and future system software).

Chroma decides how big to make its color boxes based on two things: the current depth of the device, and the size of the window. The depth determines how many boxes there will be (2 for 1-bit mode, 4 for 2-bit mode, 16 for 4-bit mode, and 256 for 8-bit mode). Actually, Chroma doesn’t really know the depth (pixel size) of a GDevice, but goes to the color table of the device’s pixMap to find out how many colors are available. You math majors out there probably noticed that with the exception of 1-bit mode, the number of colors available at each depth is a perfect square. So, a square pattern of square boxes makes the most sense for displaying the colors. The Chroma window starts out wider than it is tall, and the zooming code maintains this relationship (even on skinny monitors like Radius FPD). Chroma calculates the box size as the vertical size of the window divided by the square root of the number of colors. Once the box size is calculated, DrawWindow cycles through the pixel values as it draws color boxes, selecting colors using PmForeColor with the pixel value as its index parameter.

The data about the device are drawn in the “wider” part of the window on the right side. The strings identifying each piece of data are in resources, so ambitious users can change them to whatever they want. When the window is created, the strings are scanned to find the longest one, and that’s how much wider the window is extended. I decided to print the numbers in hexadecimal, because that is what you’d see in a debugger window. The flags and device mode are best read as binary numbers, but hex numbers are shorter and hackeroids (like me) can convert hex to binary in their heads.

Earlier, I mentioned updates coming from the DA itself. This is necessary to handle moving the window across devices of the same depth. No update event is generated by the system if it can get away with just copying the bits from one place to another. This is exactly what happens, as long as no part of the window moves to a device with a different pixel size. Since things like slot numbers and flags need to be drawn correctly, Chroma needs to know if the window has moved, so it can correctly update the data. The Desk Manager handles moving the window, without ever notifying the DA (unless part of the window requires updating, in which case an update event is eventually passed along). Well, DAs have the option of periodically being given time by the system occasionally (by setting the drvrDelay field and the needTime flag in the driver header). Chroma wakes up every 10th of a second or so and checks to see if the window has been moved since the last update event. If it has, Chroma invalidates the rectangle containing all the info, thereby generating an update event for itself.

Almost Done

WhichDevice takes a point, in global coordinates, and returns a handle to the GDevice containing that point. This function is used to figure out where to zoom the Chroma window. ZoomWindow normally fills the main device (the one with the menubar), so special care must be taken to zoom the window somewhere else. The stdState field of the WState record attached to the window contains the “zoomed” size assumed by the window in response to a ZoomWindow call with the inZoomOut part code. By setting this rectangle, Chroma controls where the window will go.

Speaking of zooming, DA’s can’t follow the “normal” detection process when it comes to the zoom box. Normally, applications call FindWindow to see which part of which window was hit by a mouseDown event. The inZoomIn and inZoomOut part codes are returned if the zoom box is hit. But, FindWindow returns inSysWindow for DA windows, no matter which part of the window is hit. DA’s can’t gain anything by calling FindWindow, because they already know the click was somewhere in a DA window! But, with a small bit of trickery, FindWindow can be fooled into thinking the DA window is an application window. The windowKind field of the window is set to the refNum of the DA when the window is opened. The refnum is always negative, and that’s how the window manager knows the window belongs to a DA. By temporarily making the windowKind positive, FindWindow returns meaningful part codes instead of inSysWindow. Once a good partCode is returned, the windowKind is made negative again.

Now for another (sort of) tricky part. Once the window is zoomed to fill a monitor, and then moved somewhere else, there’s no way to make the window small again. Hitting the zoom box makes the window fill whatever device it’s on. So, what I did was add an escape hatch. Holding the option key when hitting the zoom box will shrink the window back to its original size. If it’s already small, nothing happens.

The slot number of a given device is determined by the WhereIsTheDevice function. It takes the refNum of the driver associated with the GDevice, turns it into a unit number, looks up the device control entry in the unit table, and gets the slot number from the DCE. All this assumes the GDevice record belongs to a physical device. If the refNum is zero, indicating no driver, then the function returns an impossible slot number.

Conclusion

Don’t you hate those wind-ups where authors thank everybody they’ve ever known? Well, I don’t. I couldn’t have done this all by myself, and I want to make sure the people who helped get the credit they deserve. Here they are: First my partner Scott T. Boyd, the best spell checker I’ve ever used, for being a good sounding board. Next, Chris Derossi, Tech Support Technoid, for his good advice and unending patience with my last minute phone calls. Darin Adler, for some excellent suggestions and for being the best darned Cheese Host I’ve ever had the pleasure to meet. Now all the rest: TECHNOSTUD, Art, Howard, Doug, John, Thug, Pooter, Spaz, Ronnie, Paul, Ollie, and Bill Casey (who’s not really dead, but running the secret government).

Any questions, give me a call or drop me a line.

The MacHax™ Group

3420D Sandra St.

Bryan, TX 77801

(409)846-4102

attn: G. Marriott, M/S 27-AQ

AppleLink: D0635

MCImail: Greg Marriott

BITNET: max@tamlsr

{
 File Chroma.p
 
 This is a DA to show the current color assignments of
 all connected displays, without taking up the
 whole screen (unless you want to zoom the window!).
 
 By Greg Marriott

 Special thanks to Scott T. Boyd, Chris Derossi,
 & Darin Adler

 Copyright 1988, The MacHax™ Group.
 All rights reserved.
 
1.0d1  1-23-88    Created DA that puts up a window, and
                  plots colors of MainDevice
1.0d2  1-24-88    Made window wider, added slot number
                  of MainDevice
       1-24-88    Beefed up error detection(but not
                  necessarily correction %-)
1.0d3  1-25-88    Added brag pictures, b/w pictures
       1-25-88    Call SysEnvirons to detect colorQD
       1-25-88    Added word ‘Slot’ above slot number
1.0d4  1-26-88    Miscellaneous bug/cosmetic fixes
1.0d5  1-28-88    Made updates smarter. Now it clips to
                  each device and draws with their
                  characteristics(i.e. depth and color
                  table)
       1-28-88    Added zooming, then fixed zooming
       1-29-88    Revised zooming to fill device of
                  interest, instead of main device
1.0b1  1-29-88    Revved to beta and selected testers
1.0b2  2- 4-88    Scott made zooming work right,allowing
                  the use of FindWindow.
1.0b3  2- 7-88    Began to use Palette Manager, as Chris
                  suggested.
       2- 8-88    Added more slot info to window,
                  including gdFlags, gdRefNum, and
                  gdMode, all hex numbers.
       2- 8-88    Revised zooming, added option
                  zoom feature
1.0    2- 9-88    Published!
}

{$D+} { Debugging symbols on }

UNIT Chroma;

INTERFACE

USES
  MemTypes, QuickDraw, OSIntf, ToolIntf, PaletteMgr,
  PackIntf;


FUNCTION DRVROpen(ctlPB:ParmBlkPtr;
                  dCtl:DCtlPtr):OSErr;
FUNCTION DRVRControl(ctlPB:ParmBlkPtr;
                     dCtl:DCtlPtr):OSErr;
FUNCTION DRVRStatus(ctlPB:ParmBlkPtr;
                    dCtl:DCtlPtr):OSErr;
FUNCTION DRVRPrime(ctlPB:ParmBlkPtr;
                   dCtl:DCtlPtr):OSErr;
FUNCTION DRVRClose(ctlPB:ParmBlkPtr;
                   dCtl:DCtlPtr):OSErr;
      

IMPLEMENTATION

CONST
  versID = ‘1.0’;
  windowVSize = 96;

  bwChromaPicture = 0;
  colorChromaPicture = 1;
  sorryPicture = 2;

  infoStrings = 0;
    firstInfoStr = 1;
    slotStr = 1;
    refNumStr = 2;
    flagsStr = 3;
    modeStr = 4;
    lastInfoStr = 4;

TYPE
  ChromaStorage = RECORD
    theDevice:GDHandle;
    minSize:Point;
    windowPlace:Rect;
    hasColorQD:Boolean;
  END;
  ChromaStoragePtr = ^ChromaStorage;
  ChromaStorageHandle = ^ChromaStoragePtr;
  
  EventPtr = ^EventRecord;
  trix =  RECORD  { needed for some coercive behavior }
    CASE Boolean of
      TRUE : (dontCare:ARRAY[0..10] OF Integer);
      FALSE : (theEventPtr:  EventPtr);
    END;

  WStatePtr = ^WStateData;
  WStateHandle = ^WStatePtr;

FUNCTION RsrcID(dCtl:DCtlPtr;localID:INTEGER):Integer;
BEGIN
    { Calculate resource ID’s based on our refNum }
  RsrcID := (BOR($C000,(BSL(BNOT(dCtl^.dCtlRefNum),5))))
              + localID;
END;

FUNCTION DRVROpen(ctlPB:ParmBlkPtr;dCtl:DCtlPtr):OSErr;
  
  FUNCTION MinWindowSize:Point;
  VAR
    theStringList:Handle;
    theString:Str255;
    widest:INTEGER;
    i:INTEGER;
  BEGIN
      { The vertical minimum is predetermined }
    MinWindowSize.v := windowVSize;
    widest := 0;
    
      { Read all the strings, finding the widest one }
    FOR i := firstInfoStr TO lastInfoStr DO
    BEGIN
      GetIndString(theString, RsrcID(dCtl, infoStrings), 
                   i);
      IF StringWidth(theString) > widest THEN
        widest := StringWidth(theString);
    END;
    
      { Add a little margin }
    widest := widest + 2;
    MinWindowSize.h := windowVSize + widest;
  END; { FUNCTION MinWindowSize }

VAR   
  oldPort:GrafPtr;
  wFrame:Rect;
  myWindow:WindowPtr;
  myWindowSize:Point;
  theEnv:SysEnvRec;
  envError:OSErr;
  aPalette:PaletteHandle;

BEGIN
    { If there’s no window yet, put one up... }
  IF dCtl^.dCtlWindow = NIL THEN
  BEGIN
      { Pick a size for the window, even though we’re
        gonna change that before the window
        becomes visible }
    SetRect(wFrame, 0, 0, windowVSize, windowVSize);
    OffSetRect(wFrame, 100, 100);
    
      { Ask SysEnvirons about colorQD. If no, put up
        a “regular” window instead of a color window }
    envError := SysEnvirons(1, theEnv);
    IF theEnv.hasColorQD THEN
        myWindow := NewCWindow(NIL, wFrame, ‘Chroma’,
                      FALSE, zoomNoGrow, WindowPtr(-1),
                      TRUE, LongInt(0))
    ELSE
        myWindow := NewWindow(NIL, wFrame, ‘Chroma’,
                      FALSE, noGrowDocProc,
                      WindowPtr(-1), TRUE, LongInt(0));

      { If the window was created OK, figure out how big
        the window should be and then fill in some
        important fields }
    IF myWindow <> NIL THEN
    BEGIN
        { Start by setting the text parameters
          and computing a minimum size for the window }
      SetPort(myWindow);
      TextMode(SrcOr);
      TextFont(Geneva);
      TextSize(9);
      TextFace([]);
      myWindowSize := MinWindowSize;
      
        { Set the window to the min. size, and show it }
      SizeWindow(myWindow, myWindowSize.h,
                  myWindowSize.v, FALSE);
      ShowWindow(myWindow);
      SelectWindow(myWindow);

        { This one shows that a DA owns the window }
      WindowPeek(myWindow)^.WindowKind :=
        dCtl^.dCtlRefNum;

        { And this one lets the desk manager know, too }
      dCtl^.dCtlWindow := Ptr(myWindow);

        { We’ll keep some info in the storage field }
      dCtl^.dCtlStorage := NewHandle(SizeOf(
                             ChromaStorage));

        { Note whether we put up a color window or not }
      ChromaStorageHandle(dCtl^.dCtlStorage)^^.
        hasColorQD := theEnv.hasColorQD;
      
        { Store the min. size, based on the longest
          description name in the string list }
      ChromaStorageHandle(dCtl^.dCtlStorage)^^.
        minSize := myWindowSize;
      
      IF theEnv.hasColorQD THEN
      BEGIN
          { Get the main device, then note the window’s
            global location }
        WITH ChromaStorageHandle(dCtl^.dCtlStorage)^^ DO
        BEGIN
          theDevice := GetMainDevice;
          windowPlace := WindowPeek(dCtl^.dCtlWindow)^.
                          contRgn^^.rgnBBox;
        END;
        
          { Make a new palette, and “install” it }
        aPalette := NewPalette(256, NIL, pmExplicit, 0);
        SetPalette(myWindow, aPalette, TRUE);
      END;
    END;{ if window was created ok... }
  END;{ if window doesn’t exist... }
  DRVROpen := NOErr;
END;

FUNCTION DRVRClose(ctlPB:ParmBlkPtr;dCtl:DCtlPtr):OSErr;
BEGIN
    { If there’s a window up, get rid of it,
      and let the desk manager know, too }
  IF dCtl^.dCtlwindow <> NIL THEN
  BEGIN
    DisposeWindow(WindowPtr(dCtl^.dCtlWindow));
    dCtl^.dCtlWindow := NIL;
  END;

    { If we created storage, get rid of it }
  IF dCtl^.dCtlStorage <> NIL THEN
    DisposHandle(dCtl^.dCtlStorage);

  DRVRClose := NOErr;
END;

FUNCTION DRVRControl(ctlPB:ParmBlkPtr;
                     dCtl:DCtlPtr):OSErr;

  FUNCTION WhereIsTheDevice(whatDevice:GDHandle):
            INTEGER;
  CONST
    UTableBase = $11c;
  VAR
    devRefNum:Longint;
    unitTablePtr:^Ptr;
    unitTableBase:Ptr;
    theDCEHandle:AuxDCEHandle;
    theDCEHandlePtr:^AuxDCEHandle;
  BEGIN
      { The refnum of the gdevice we’re interested in }
    devRefNum := whatDevice^^.gdRefNum;

      { If it’s zero, return an impossible slot number }
    IF devRefNum = 0 THEN
    BEGIN
      WhereIsTheDevice := 42;
      Exit(WhereIsTheDevice);
    END;
    
      { Turn it into a unit number }
    devRefNum := BNOT(devRefNum);
    
      { Grab the unit table address }
    unitTablePtr := Pointer(UTableBase);
    unitTableBase := unitTablePtr^;
    
      { Go get the address of the device control entry
        for this unit }
    theDCEHandlePtr := Pointer(Ord4(unitTableBase)
                        + devRefNum * 4);
    theDCEHandle := theDCEHandlePtr^;
    
      { Return the slot number of this driver }
    WhereIsTheDevice := theDCEHandle^^.dCtlSlot;
  END;{ FUNCTION WhereIsTheDevice }

  PROCEDURE CenterInWindow(VAR theRect:Rect);
  VAR
    rectSize:Point;
    chromaSize:Point;
  BEGIN
      { “Home” the rect first }
    OffsetRect(theRect, -theRect.left, -theRect.top);

      { Figure size of rect }
    WITH theRect DO
      SetPt(rectSize, right, bottom);

      { Figure size of window }
    WITH GrafPtr(dCtl^.dCtlWindow)^.portRect DO
      SetPt(chromaSize, right - left, bottom - top);

      { Position the rect, centered in the window }
    OffsetRect(theRect, (chromaSize.h - rectSize.h)
                DIV 2, (chromaSize.v - rectSize.v)
                DIV 2);
  END;{ PROCEDURE CenterInWindow }

  PROCEDURE DrawWindow;
  
    PROCEDURE DrawNextString(VAR drawWhere:Point;
                              drawWhat:Str255;
                              drawHow:Style);
    VAR
      someFontInfo:FontInfo;
      oldFace:Style;
    BEGIN
        { Save the text style }
      oldFace := GrafPtr(dCtl^.dCtlWindow)^.txFace;
        { Set the desired text face }
      TextFace(drawHow);
      
        { The “cursor” will be centered already, so move
          back half the width and draw it. }
      Move(-(StringWidth(drawWhat) DIV 2), 0);
      DrawString(drawWhat);
      
        { Move the “cursor” up a line, since
          we’re drawing from the bottom of the window
          toward the top. We’re letting the descenders
          overhang, since textmode has been set to SrcOr 
          and won’t wipe out the overlap. }
      GetFontInfo(someFontInfo);
      drawWhere.v := drawWhere.v - someFontInfo.ascent;
        { Re-center the “cursor” for the next time }
      MoveTo( drawWhere.h, drawWhere.v );
      
        { Restore text face }
      TextFace(oldFace);
    END;{ PROCEDURE DrawNextString }
    
    PROCEDURE NumToHexString(aNumber:INTEGER;
                              VAR aString:Str255);
      { Make a 4 digit hexadecimal number
        from an integer }
    VAR
      unsignedNum:LONGINT;
      i:INTEGER;
      aDigit:INTEGER;
    BEGIN
        { Make an unsigned hex number from the
          signed integer }
      IF aNumber>0 THEN
        unsignedNum := aNumber
      ELSE
        unsignedNum := aNumber + 65536;
      
        { Make sure the string has 4 digits (spaces)}
      aString := ‘    ‘;
      
        { Fill in the digits, from lsd to msd }
      FOR i := 4 DOWNTO 1 DO
      BEGIN
        aDigit := unsignedNum MOD 16;
        IF aDigit<10 THEN
          aString[i] := chr(ord(‘0’)+aDigit)
        ELSE
          aString[i] := chr(ord(‘A’)+aDigit-10);
        unsignedNum := unsignedNum DIV 16;
      END;
    END;{ PROCEDURE NumToHexString }

  VAR 
    howManyColors:INTEGER;
    pixPerSide:Point;
    pixSize:Point;
    portSize:Point;
    pixNumber:INTEGER;
    oldIndex:INTEGER;
    i,j:INTEGER;
    slotNumberString:Str255;
    theFontInfo:FontInfo;
    sorryPict:Handle;
    sorryRect:Rect;
    aPalette:PaletteHandle;
    cursorPt:Point;
    theString:Str255;
  BEGIN
    IF dCtl^.dCtlWindow <> NIL THEN
    BEGIN
      WITH ChromaStorageHandle(dCtl^.dCtlStorage)^^ DO
      BEGIN
          { Prepare to draw the contents of the window }
        EraseRect(GrafPtr(dCtl^.dCtlWindow)^.portRect);
  
          { On a color Mac with CLUT device, show the
            colors, on other machines, a warning }
        IF hasColorQD AND (theDevice^^.gdType=clutType)
        THEN
          BEGIN
              { What is the size of our window? }
            WITH GrafPtr(dCtl^.dCtlWindow)^.portRect DO
              SetPt(portSize, right - left,
                              bottom - top);
            
              { We need to know how many colors are in
                the clut of the device of interest }
            howManyColors := theDevice^^.gdPMap^^
                             .pmTable^^.ctSize + 1;
      
              { Assume a square arrangement of colors,
                except for 2 color mode. Calculate pixel
                size based on vertical size of window,
                assuming that the window will always
                be wider than it is tall }
            pixPerSide.v := Round(sqrt(howManyColors));
            IF howManyColors = 2 THEN
              pixPerSide.h := 2
            ELSE
              pixPerSide.h := pixPerSide.v;
  
            pixSize.v := portSize.v DIV pixPerSide.v;
            IF howManyColors = 2 THEN
              pixSize.h := pixSize.v DIV 2
            ELSE
              pixSize.h := pixSize.v;
  
            PenSize(pixSize.h, pixSize.v);
            
              { Keep track of the pixel number and use
                it to plot the colors in the palette
                we’ll fill from the device’s CLUT }
            pixNumber := 0;
            
              { Fill the palette with the colors from
                the current device, and activate the
                changes }
            aPalette := GetPalette(WindowPtr(dCtl^
                                   .dCtlWindow));
            CTab2Palette(theDevice^^.gdPMap^^.pmTable,
                         aPalette, pmExplicit,0);
            ActivatePalette(WindowPtr(dCtl^
                            .dCtlWindow));
            
              { Plot colored pixels one row at a time,
                ‘til they’re all used up }
            FOR i := 0 TO(pixPerSide.v - 1) DO
              FOR j := 0 TO(pixPerSide.h - 1) DO
              BEGIN
                  { Set the foreColor, and draw a dot }
                PmForeColor(pixNumber);  
                MoveTo(j * pixSize.h, i * pixSize.v);
                Line(0, 0);
  
                pixNumber := pixNumber + 1;
              END;{ Plotting loop... }
                  
              { Put up some device info, first figuring
                some window positions to put the text,
                starting at the bottom of the window and 
                centered in the blank part of the
                window }
            SetPt(cursorPt, portSize.v + (portSize.h - 
                    portSize.v) DIV 2, portSize.v - 2 );
            MoveTo( cursorPt.h, cursorPt.v );
            
              { Put up the mode, then its rsrc string }
            NumToHexString(theDevice^^.gdMode,
                           theString);
            DrawNextString(cursorPt, theString, [bold]);
            GetIndString(theString, RsrcID(dCtl,
                          infoStrings), modeStr);
            DrawNextString(cursorPt, theString, []);

              { Put up flags, then their rsrc string }
            NumToHexString(theDevice^^.gdFlags,
                           theString);
            DrawNextString(cursorPt, theString, [bold]);
            GetIndString(theString, RsrcID(dCtl,
                          infoStrings), flagsStr);
            DrawNextString(cursorPt, theString, []);

              { Put up refNum, then its rsrc string }
            NumToHexString(theDevice^^.gdRefNum,
                           theString);
            DrawNextString(cursorPt, theString, [bold]);
            GetIndString(theString, RsrcID(dCtl,
                          infoStrings), refNumStr);
            DrawNextString(cursorPt, theString, []);
  
              { Put up the slot#, then its rsrc string }
            NumToHexString(WhereIsTheDevice(theDevice) - 
                           8, theString);
            DrawNextString(cursorPt, theString, [bold]);
            GetIndString(theString, RsrcID(dCtl,
                          infoStrings), slotStr);
            DrawNextString(cursorPt, theString, []);

          END { if on a mac II... }
        ELSE
          BEGIN
              { For non-color Macs, or non-clut devices,
                show a picture saying why Chroma isn’t
                showing pretty colors... }
            sorryPict := GetResource(‘PICT’,
                           RsrcID(dCtl, sorryPicture));
  
            IF sorryPict <> NIL THEN
            BEGIN
                { Center the picture in the window,
                  and draw it }
              sorryRect := PicHandle(sorryPict)^^
                             .picFrame;
              CenterInWindow(sorryRect);
  
              DrawPicture(PicHandle(sorryPict),
                          sorryRect);
              ReleaseResource(sorryPict);
            END;{ if picHandle is good... }
          END;{ non-color/non-clut condition }
  
          { Put up the version number in the
            top right corner}
        GetFontInfo(theFontInfo);
        MoveTo(GrafPtr(dCtl^.dCtlWindow)^.portRect.
               right - StringWidth(versID), theFontInfo.
               ascent);
        DrawString(versID);
      END; { WITH ChromaStorage... }
    END;{ if window exists... }
  END;{ PROCEDURE DrawWindow }
  
  FUNCTION WhichDevice(aPoint:Point):GDHandle;
  VAR
    aDevice:GDHandle;
    foundOne:Boolean;
  BEGIN
      { Get first one, and set the initial condition }
    aDevice := GetDeviceList;
    foundOne := FALSE;

    WHILE (aDevice <> NIL) AND NOT foundOne DO
      { assuming it has to be in one of the devices... }
    BEGIN
        { Check to see if this is the one... }
      IF PtInRect(aPoint, aDevice^^.gdRect) THEN
      BEGIN
        WhichDevice := aDevice;
        foundOne := TRUE;
      END;
        { Get the next device in the list }
      aDevice := aDevice^^.gdNextGD;
    END;
  END;{ FUNCTION WhichDevice }
  
  FUNCTION EqualRectSize(rect1, rect2:Rect):Boolean;
    { This function is dedicated to Scott T. Boyd %-)}
  BEGIN
    EqualRectSize :=((rect1.right - rect1.left) =
                      (rect2.right - rect2.left)) AND
                      ((rect1.bottom - rect1.top) =
                      (rect2.bottom - rect2.top));
  END;{ FUNCTION EqualRectSize }
  
  PROCEDURE ZoomIt(partCode:INTEGER; clickedWhere:Point;
                    optKeyDown:Boolean);
  CONST
    mBarHeight = $BAA;
  VAR
    oldRect, newRect:Rect;
    maxHeight:INTEGER;
    menuBarHeight:^INTEGER;
    doZoom:Boolean;
  BEGIN
      { Assume we’ll zoom }
    doZoom := TRUE;
      { Get the old window size, described by the
        content region }
    oldRect := WindowPeek(dCtl^.dCtlWindow)^.
                contRgn^^.rgnBBox;
    
      { If the optionKey is down, shrink the window to
        original size... unless, of course, it’s already
        original size. }
    IF optKeyDown THEN BEGIN
      newRect := oldRect;
      newRect.left := newRect.right -
                        ChromaStorageHandle(dCtl^.
                        dCtlStorage)^^.minSize.h;
      newRect.bottom := newRect.top +
                          ChromaStorageHandle(dCtl^.
                          dCtlStorage)^^.minSize.v;

        { If it’s not already small, make it small,
          otherwise DON’T ZOOM THE WINDOW! }
      IF NOT EqualRect(oldRect,newRect) THEN
        WITH WindowPeek(dCtl^.dCtlWindow)^ DO
          wStateHandle(dataHandle)^^.stdState := newRect
      ELSE
        doZoom := FALSE;
    END
    ELSE BEGIN
        { Figure out which device the zoom box was on,
          so we know which monitor to fill up with
          the window. }
      newRect := WhichDevice(clickedWhere)^^.gdRect;
      InsetRect(newRect, 3, 3);
      newRect.top := newRect.top + 18;{ titlebar }
        { If it’s the main device, make room for
          menu bar }
      IF WhichDevice(clickedWhere)=GetMainDevice THEN
      BEGIN
        menuBarHeight := Pointer( mBarHeight );
        newRect.top := newRect.top + menuBarHeight^;
      END;
  
        { Make sure that the window will be wider than
          it is tall. It should be no taller than its
          width minus the slot info area on the right
          side.  The info area’s size can be calculated
          from the minSize width - minSize height. }
      WITH ChromaStorageHandle(dCtl^.dCtlStorage)^^ DO
        maxHeight := newRect.right - newRect.left -
                      (minSize.h - minSize.v);
        { If it’s higher than it should be, shorten it }
      IF newRect.bottom - newRect.top > maxHeight THEN
        newRect.bottom := newRect.top + maxHeight;
      
        { If we’re not already a big window, zoom to it,
          by putting the new size in stdState.
          Otherwise, leave the old size there
          (from last time)}
      IF NOT EqualRect(oldRect, newRect) THEN
        WITH WindowPeek(dCtl^.dCtlWindow)^ DO
          wStateHandle(dataHandle)^^.stdState :=
            newRect;
    END;{ if not optionkey... }

    IF doZoom THEN
    BEGIN
      EraseRect(GrafPtr(dCtl^.dCtlWindow)^.portRect);
      ZoomWindow(WindowPtr(dCtl^.dCtlWindow), partCode,
                  false);
      InvalRect(GrafPtr(dCtl^.dCtlWindow)^.portRect);

        { Fool ZoomWindow into always zooming “out” by
          changing the “zoomed” window size }
      WITH WindowPeek(dCtl^.dCtlWindow)^ DO
        wStateHandle(dataHandle)^^.stdState := oldRect;
    END;
  END;{ PROCEDURE ZoomIt }
  
  PROCEDURE BragALittle;
  VAR
    aboutPict:Handle;
    aboutRect:Rect;
  BEGIN
    WITH ChromaStorageHandle(dCtl^.dCtlStorage)^^ DO
    BEGIN
      EraseRect(GrafPtr(dCtl^.dCtlWindow)^.portRect);
      
        { If they’re not on a color Mac, or there’s less
          than 16 colors, put up the monochrome version
          of the brag picture.  BTW, the boolean short-
          circuits on non-color Macs so Chroma won’t
          try to access non-existent data structures }
      IF (NOT hasColorQD) |
          (theDevice^^.gdPMap^^.pmTable^^.ctSize + 1 <
            16)
      THEN
        aboutPict := GetResource(‘PICT’,
                          RsrcID(dCtl, bwChromaPicture))
      ELSE
        aboutPict := GetResource(‘PICT’,
                          RsrcID(dCtl,
                                 colorChromaPicture));
    
      IF aboutPict <> NIL THEN
      BEGIN
          { Center the picture, and draw it }
        aboutRect := PicHandle(aboutPict)^^.picFrame;
        CenterInWindow(aboutRect);
    
        DrawPicture(PicHandle(aboutPict), aboutRect);
        ReleaseResource(aboutPict);
      END;
      
        { Wait until the button’s not down
          (Hi Roger %-) }
      REPEAT UNTIL NOT StillDown;
      
        { Restore the contents of the window }
      InvalRect(GrafPtr(dCtl^.dCtlWindow)^.portRect);
    END;{ WITH ... }
  END;{ PROCEDURE BragALittle }

VAR
  eventAt:  EventPtr;
  oldPort:GrafPtr;
  localPoint:Point;
  aDevice:GDHandle;
  clippyPart:Rect;
  oldClip:RgnHandle;
  thePartCode:INTEGER;
  whichWindow:WindowPtr;
  intersections:INTEGER;
  dumbRect:Rect;
  
BEGIN { of DRVRControl }
  WITH ChromaStorageHandle(dCtl^.dCtlStorage)^^ DO
  BEGIN
    GetPort(oldPort);
    SetPort(GrafPtr(dCtl^.dCtlWindow));

    CASE ctlPB^.csCode OF
      accEvent:  
        BEGIN
            { Get the event pointer, through some
              coercive trickery }
          eventAt := trix(ctlPB^.CSParam).theEventPtr;
          WITH eventAt^ do
          BEGIN
            CASE what OF
              updateEvt:
                BEGIN
                    { Save the current clip region, and
                      restore it after the update }
                  oldClip := NewRgn;
                  GetClip(oldClip);
                  BeginUpdate(WindowPtr(eventAt^.
                                message));
                    { If there’s no ColorQD, just draw
                      the  window; otherwise cycle
                      through all the devices, clipping
                      the window to each device }
                  IF NOT hasColorQD THEN
                    DrawWindow
                  ELSE BEGIN
                    aDevice := GetDeviceList;             
                      { Go until the end of the list }
                    WHILE aDevice <> NIL DO
                    BEGIN
                        { Check for intersection of the
                          content rgn with the device }
                      WITH WindowPeek(dCtl^.dCtlWindow)^ 
                      DO IF SectRect(contRgn^^.rgnBBox,
                                     aDevice^^.gdRect,
                                     clippyPart) THEN
                      BEGIN
                          { Translate the global rect
                            to local coordinates }
                        GlobalToLocal(clippyPart.
                                      topLeft);
                        GlobalToLocal(clippyPart.
                                      botRight);
                        
                          { Set the clip, so other parts 
                            don’t get blasted.
                            Set theDevice field of the
                            storageHandle to the device
                            of interest, then draw }
                        ClipRect(clippyPart);
                        theDevice := aDevice;
                        DrawWindow;
                      END;{ if intersect... }
                      { Go to the next device in the
                        device list }
                    aDevice := aDevice^^.gdNextGD;
                    END;{ while there’s more devices...}
                  END;{ if a color machine... }

                  EndUpdate(WindowPtr(eventAt^.
                            message));
                  
                    { Restore the clip, axe the region }
                  SetClip(oldClip);
                  DisposeRgn(oldClip);

                    { Mark the window’s position }
                  windowPlace := WindowPeek(dCtl^.
                        dCtlWindow)^.contRgn^^.rgnBBox;
                END;
              mouseDown:
                BEGIN
                  localPoint := where;
                  GlobalToLocal(localPoint);
  
                  { Pretend this isn’t a DA window to
                    fool FindWindow }
                  WITH WindowPeek(dCtl^.dCtlWindow)^ DO
                    windowKind := -windowKind;
                  thePartCode := FindWindow(where,
                                  WindowPtr(dCtl^.
                                  dCtlWindow));
                  WITH WindowPeek(dCtl^.dCtlWindow)^ DO
                    windowKind := -windowKind;
                  
                    { In zoom box, do it, passing along
                      the state of the option key... }
                  IF (thePartCode=inZoomIn) OR
                      (thePartCode=inZoomOut) THEN
                  BEGIN
                    IF TrackBox(WindowPtr(dCtl^
                                .dCtlWindow), where,
                                thePartCode) THEN
                      ZoomIt(thePartCode, where,
                              BitAnd(modifiers,
                                     optionKey)<>0);
                  END ELSE
                      { See if they clicked on the vers.
                        number.  If so, put up a brag 
                        picture ‘til they release the
                        button }
                    WITH localPoint,
                        GrafPtr(dCtl^.dCtlWindow)^.
                          portRect DO
                      IF (h > right-StringWidth(versID))
                          AND (v < 12) THEN
                      BEGIN
                        BragALittle;
                      END;{ if h and v in range... }
                END;{ mouseDown case }
            END;{ case what ... }
          END;{ with eventAt... }
        END;{ accEvent Case }

      accRun:   
        BEGIN      { the periodic call }
          WITH ChromaStorageHandle(dCtl^.
                 dCtlStorage)^^ DO
          BEGIN
              { This is a problem on multiple device
                systems, check for CQD }
            IF hasColorQD THEN
            BEGIN
                { Moved? If yes, inval the info part
                  of the window }
              IF NOT EqualRect(WindowPeek(dCtl^.
                               dCtlWindow)^.
                               contRgn^^.rgnBBox,
                               windowPlace) THEN
              BEGIN
                clippyPart :=GrafPtr(dCtl^.dCtlWindow)^.
                                      portRect;
                clippyPart.left := clippyPart.left +
                                    clippyPart.bottom;
                InvalRect(clippyPart);
              END;{ if window moved... }
            END;{ if has color quickdraw... }
          END;{ with chromastorage... }
        END;{ accRun case... }
    END;{ case ctlPB^.csCode }
    
    SetPort(oldPort);
    DRVRControl := NoErr;
  END;{ with dctl^.dctlstorage... }
END;{ of DRVRControl }

FUNCTION DRVRPrime(ctlPB:ParmBlkPtr;dCtl:DCtlPtr):OSErr;
BEGIN
  DRVRPrime := NoErr;
END;

FUNCTION DRVRStatus(ctlPB:ParmBlkPtr;dCtl:DCtlPtr):OSErr;
BEGIN
  DRVRStatus := NoErr;
END;
END. {of Chroma UNIT}

Chroma Make File for MPW

Chroma.DA  ƒ  Chroma.DRVW Chroma.r
  Rez -rd -c DMOV -t DFIL Chroma.r -o Chroma.DA
Chroma.DRVW   ƒ  Chroma.p.o
  Link -w -rt DRVW=0 
    -sg Chroma 
    “{Libraries}”DRVRRuntime.o 
    Chroma.p.o 
    “{Libraries}”Interface.o 
    “{PLibraries}”Paslib.o 
    -o Chroma.DRVW -c “????” -t “????”
Chroma.p.o  ƒ  Chroma.p
  Pascal Chroma.p

Chroma Resource File in REZ Format

/*
 * File Chroma.r
 *
 * Copyright The MacHax™ Group, 1988
 * All rights reserved.
 *
 */
#include “Types.r”        /* To get system types */
#include “MPWTypes.r”     /* To get ‘DRVW’ type */

type ‘DRVR’ as ‘DRVW’;    /* Map ‘DRVW’ => ‘DRVR’ */
/*
 * This will produce a DRVR resource from the special
 * DRVW type.
 *
 * Note that the ID 12 is irrelevant, since the
 * Font/DA Mover will renumber it
 * to something else when installing it anyway.
 *
 * The leading NUL in the resource name is required to
 * conform to the desk accessory naming convention.
 *
 * The resource is declared purgeable.  If the code were
 * to do funky things like SetTrapAddress calls
 * (requiring the code to be around at all times), we
 * would have to set it nonpurgeable.
 */

#define DriverID  12
resource ‘DRVR’ (DriverID, “\0x00Chroma”, purgeable) {
  /*
   * DRVR flags
   */
  dontNeedLock,           /* OK to float around */
  needTime,               /* Periodic Control calls */
  dontNeedGoodbye,        /* No special requirements */
  noStatusEnable,
  ctlEnable,              /* Enable Control calls */
  noWriteEnable,
  noReadEnable,
  6,                      /* drvrDelay - 1/10 second */
  updateMask + mDownMask, /* drvrEMask - Event mask */
  0,                      /* drvrMenu - No menu */
  “Chroma”,               /* drvrName */
  /*
   * This directive inserts the contents of the
   * DRVW resource produced by linking DRVRRuntime.o
   * with our DA code
   */
  $$resource(“Chroma.DRVW”, ‘DRVW’, 0)
};

#define infoStrings 0
resource ‘STR#’ ( ( 0xC000 | ( DriverID << 5 ) ) +
                  infoStrings ) {
  {
    “Slot”;
    “gdRefNum”;
    “gdFlags”;
    “gdMode”
  };
};

#define bwChromaPicture 0
#define colorChromaPicture 1
#define sorryPicture 2
resource ‘PICT’ ( ( 0xC000 | ( DriverID << 5 ) ) +
                  colorChromaPicture ) {
  2504,
  {13, 137, 96, 265},
  $”0011 02FF 0C00 FFFF FFFF 0089 0000 000D”
  $”0000 0109 0000 0060 0000 0000 0000 001E”
  $”0001 000A 0000 0000 015E 01B8 0098 8040"
  $”000D 0089 0060 0109 0000 0000 0000 0000"
  $”0048 0000 0048 0000 0000 0004 0001 0004"
  $”0000 0000 0000 1F10 0000 0000 0000 0004"
  $”8000 000F 0000 FFFF FFFF FFFF 0000 FC00"
  $”F37D 052F 0000 FFFF 648A 028C 0000 DD6B”
  $”08C2 06A2 0000 F2D7 0856 84EC 0000 46E3"
  $”0000 A53E 0000 0000 0000 D400 0000 0241"
  $”AB54 EAFF 0000 1F21 B793 1431 0000 0000"
  $”64AF 11B0 0000 5600 2C9D 0524 0000 90D7"
  $”7160 3A34 0000 C000 C000 C000 0000 8000"
  $”8000 8000 0000 4000 4000 4000 0000 0000"
  $”0000 0000 000D 0089 0060 0109 000D 0089"
  $”0060 0109 0000 02C1 0002 C100 02C1 0008"
  $”F000 0201 1110 D500 0EF7 0000 03FE 33FE”
  $”0002 1111 10D5 000F F800 0003 FD33 0530"
  $”0000 1111 10D5 000B F800 FB33 0300 0111"
  $”11D4 0010 F900 0003 FE33 0603 3333 0001"
  $”1111 D400 21F9 00FE 3307 0000 3333 0001"
  $”1110 FC00 0188 88FA 0003 0777 7770 F100"
  $”FE44 0040 FA00 26F9 0008 3333 3000 0333"
  $”3300 01FD 1102 1000 00FC 8803 8000 0007"
  $”FD77 0100 00FC 66F9 00FB 44FB 0029 FA00"
  $”0803 3333 0000 0333 3300 FB11 0100 00FB”
  $”8801 0000 FC77 0170 00FC 6600 60FE 66FE”
  $”0000 04FB 44FB 002B FA00 0803 3333 0000"
  $”0333 3000 FB11 0210 0008 FC88 0100 07FC”
  $”7701 7000 F866 0260 0000 FE44 0340 0444"
  $”44FB 002E FA00 0203 3330 FB00 FB11 0810"
  $”0008 8888 8088 8800 FE77 0400 0777 7000"
  $”FE66 0006 FB66 0800 0444 4440 0004 4444"
  $”FB00 30FA 0002 0333 30FB 00FE 1107 1001"
  $”1110 0008 8888 FD00 0B77 7770 0007 7770"
  $”0066 6660 00FB 6608 0004 4444 0000 0444"
  $”40FB 0034 FA00 0203 3330 FB00 FE11 0710"
  $”0111 1000 8888 80FE 000C 0777 7700 0007"
  $”7770 0066 6660 00FE 660B 0066 6600 4444"
  $”4000 0044 4440 FB00 34FA 0002 0333 30FB”
  $”00FE 1107 0001 1110 0088 8880 FE00 1B07"
  $”7777 0000 0777 7006 6666 0000 6666 6000"
  $”6666 0044 4440 0000 4444 40FB 0032 FA00"
  $”0203 3330 FB00 FE11 0600 0111 1000 8888"
  $”FD00 1A07 7770 0000 0777 7006 6666 0006"
  $”6666 0000 6666 0044 4400 0004 4444 FA00"
  $”32FA 0002 0333 30FB 00FE 1106 0011 1110"
  $”0088 88FD 001A 0777 7000 0077 7770 0666"
  $”6000 0666 6600 0066 6600 4444 0000 0444"
  $”44FA 0032 FA00 0203 3333 FB00 0911 1110"
  $”0011 1110 0888 88FD 0017 0777 7000 0077"
  $”7770 0666 6000 0666 6000 0066 6600 4444"
  $”0000 FE44 FA00 35FA 0012 0333 3300 0003"
  $”3330 0011 1110 0011 1100 0888 88FD 0017"
  $”0777 7000 0777 7770 6666 6000 0666 6000"
  $”0666 6600 4444 4004 FE44 FA00 2FF9 00FE”
  $”330E 0033 3330 0011 1110 0111 1100 0888"
  $”80FD 0003 0777 7707 FE77 0C00 6666 6000"
  $”6666 6000 0666 6600 FA44 FA00 2CF9 00FB”
  $”330B 3000 1111 0001 1111 0008 8880 FD00"
  $”0007 FC77 0D70 0066 6600 0066 6660 0006"
  $”6660 00FA 4400 40FB 002D F900 0003 FC33"
  $”0B00 0011 1100 0111 1000 0888 80FC 00FC”
  $”770E 0000 6666 0000 6666 0000 0666 6000"
  $”04FB 4400 40FB 0033 F800 0003 FE33 0C30"
  $”0000 1111 0001 1110 0008 8880 FC00 0007"
  $”FE77 FE00 0C66 6600 0066 6600 0006 6660"
  $”0000 FE44 0300 0444 40FB 0002 C100 02C1"
  $”0002 C100 02C1 0002 C100 0BFE 0001 0FF0"
  $”E400 00FF E400 20FE 0001 0FF0 F700 010F”
  $”FFF1 0004 0FFF 000F F0F4 0000 FFFC 0004"
  $”0FF0 0000 FFFF 001B FE00 00FF F700 010F”
  $”FFF0 0004 0FFF 00FF F0EE 0004 0FF0 0000"
  $”FFFF 003F FE00 07FF FFF0 00FF 000F F0FE”
  $”0000 FFFE 000A 0FFF FFF0 0FFF F000 00FF”
  $”F0FD 0009 FFFF 0FFF F000 0FFF FF00 FEFF”
  $”090F FFFF F00F F000 0FFF 00FE FF04 0FFF”
  $”FFF0 003E FE00 0BFF F0FF 00FF 000F F000"
  $”000F F0FE 000A 0FFF 0000 FF00 FF00 0FF0"
  $”FFFD 00FE FF19 0FF0 00FF 00FF 00FF F000"
  $”0FFF 0000 0FF0 00FF 0FF0 00FF 0000 0FF0"
  $”FF00 40FE 0006 FF00 0FF0 FF00 FFFE 000F”
  $”0FF0 0FFF 000F F000 0FF0 00FF 00FF 00FF”
  $”FE00 1D0F F0FF FF0F F00F F000 FF00 FF00"
  $”000F F000 000F F00F F00F F000 FF00 000F”
  $”F0FF 0040 FE00 06FF 000F F00F FFF0 FE00"
  $”0F0F F0FF 0FF0 0FF0 000F FFFF F000 FF00"
  $”FFFE 001D 0FF0 FFF0 FF00 FF00 0FF0 00FF”
  $”0000 0FF0 0000 0FF0 FF00 0FF0 00FF 0000"
  $”0FF0 FF00 4009 0000 0FF0 000F F00F FFF0"
  $”FE00 0F0F F000 0FF0 FF00 000F F000 000F”
  $”F00F FFFE 000E 0FF0 FF00 FF00 FF00 0FF0"
  $”0FF0 0000 FFFE 000A FF00 FF00 0FF0 0FF0"
  $”0000 FFFE 003E 0800 000F F000 FF00 00FF”
  $”FC00 0EFF 00FF 00FF 0000 0FF0 0FF0 0FF0"
  $”FFFF FE00 0EFF 0000 0FF0 00FF 00FF F00F”
  $”F000 00FF FE00 0AFF 00FF 00FF 000F F000"
  $”00FF FE00 3E08 0000 0FFF FFF0 0000 FFFC”
  $”0004 0FFF F000 FFFE 0006 FFFF 0000 FFFF”
  $”F0FE 000E FF00 000F F000 0FFF FFF0 0FF0"
  $”0000 FFFE 000A FF00 0FFF F000 0FF0 0000"
  $”FFFE 000C FA00 010F F0EF 0001 0FF0 DE00"
  $”0DFA 0001 0FF0 F100 020F F0FF DD00 0BFA”
  $”0000 FFEF 0001 FFF0 DD00 02C1 0002 C100"
  $”02C1 0002 C100 02C1 0002 C100 02C1 0002"
  $”C100 02C1 0002 C100 02C1 0002 C100 02C1"
  $”0002 C100 0703 000F FFF0 C500 3215 00F0"
  $”000F 0000 F000 0FFF 000F FF00 0FFF 0000"
  $”0FFF FF0F FB00 03F0 0000 F0FC 0002 F000"
  $”F0FC 0008 0FFF F000 F000 00FF F0F7 0031"
  $”150F 00FF 00F0 0FF0 00F0 00F0 F000 F0F0"
  $”00F0 0000 0F00 0FFB 0003 FF00 0FF0 FC00"
  $”02F0 00F0 FB00 07F0 FF0F F000 0F00 0FF7"
  $”003F 1B0F 0F00 00F0 00F0 00F0 00F0 F000"
  $”F0F0 00F0 0000 0F00 0FFF 000F F000 00FD”
  $”F00D 0FF0 00FF 00F0 00F0 0FF0 0F00 0F00"
  $”FDF0 0D00 0F00 000F 0FF0 0FF0 0F00 F0FF”
  $”F041 0F0F 0F00 00F0 00F0 000F FFF0 0FFF”
  $”000F FFFE 002C 0F00 0F00 F0F0 0F00 00F0"
  $”0F00 F000 0F0F 00F0 FFFF F000 0F00 F0F0"
  $”00F0 F000 F000 0F00 FF0F F000 F00F 0F00"
  $”F0F0 0F3D 060F 00FF 00F0 00F0 FE00 21F0"
  $”F000 F0F0 00F0 0000 0F00 0F00 F0FF FF00"
  $”00F0 0000 F00F FF0F 0000 F000 F00F FF00"
  $”0FFA 000C 0F00 0F0F 0000 F00F 0F00 F0F0"
  $”0F3E 1800 F000 0F00 00F0 0000 0F00 F000"
  $”F0F0 00F0 0000 0F00 0F00 F0F0 FE00 10F0"
  $”0000 F0F0 0F0F 00F0 F000 F0F0 0F00 F0F0"
  $”FB00 0C0F 000F 0F00 00F0 0F0F 00F0 F00F”
  $”3D0F 000F FFF0 0000 F000 0FF0 000F FF00"
  $”0FFF FE00 190F 000F 00F0 0FF0 0000 F000"
  $”00F0 0FFF 00FF 00F0 00F0 0FFF 0F00 0FFA”
  $”000B FFF0 0F00 000F F000 FFF0 FFF0 05C3"
  $”0001 F000 05C3 0001 F000 02C1 0002 C100"
  $”02C1 001F F600 10F0 00FF 0FF0 000F FFF0"
  $”00F0 0000 0F00 000F FC00 01FF FFEF 0000"
  $”F0F7 001F F600 08F0 000F 00F0 000F 000F”
  $”FD00 030F 0000 0FFC 0002 F000 F0F0 0000"
  $”F0F7 0031 F700 2B0F 0F00 0F00 F000 0F00"
  $”0F0F F00F FF0F FF00 FFF0 0FFF 0000 F000"
  $”F00F F000 FFF0 0FF0 0F0F F0F0 00F0 0FF0"
  $”00FF F0F7 0031 F700 130F 0F00 0F00 F000"
  $”0FFF F000 F0F0 0F0F 00F0 0F00 F0FE 0014"
  $”FFFF 00F0 0F0F 0000 F00F 0FF0 000F 0F00"
  $”F00F 0F00 F0F7 0031 F700 2BFF FFF0 0F00"
  $”F000 0F0F 0000 F0F0 0F0F 00F0 0F00 0FF0"
  $”0000 F0F0 00FF FF00 FF00 FFFF 0F00 000F”
  $”0F00 FFFF 0F00 F0F7 0031 F700 1AF0 00F0"
  $”0F00 F000 0F00 F000 F0F0 0F0F 00F0 0F00"
  $”000F 0000 F00F 00F0 FE00 03F0 F000 0FFE”
  $”0006 F000 F000 0F00 F0F7 0032 F700 21F0"
  $”00F0 0F00 F000 0F00 0F00 F00F FF0F 00F0"
  $”00F0 FFF0 0000 F000 F00F F00F FF00 0FF0"
  $”0FFE 0007 F000 0FF0 00FF F00F F800 06EA”
  $”0000 0FD9 0007 EB00 010F F0D9 0002 C100"
  $”02C1 0002 C100 02C1 0002 C100 00FF”
};

resource ‘PICT’ ( ( 0xC000 | ( DriverID << 5 ) ) +
                  bwChromaPicture ) {
  1023,
  {83, 167, 166, 295},
  $”1101 A000 8201 000A 0000 0000 02D0 0240"
  $”9800 1200 5300 A000 A601 2800 5300 A700"
  $”A601 2700 5300 A700 A601 2700 0002 EF00"
  $”02EF 0002 EF00 06FC 0000 3CF5 0008 FE00"
  $”020F E07C F500 08FE 0002 3FF0 7CF5 0008"
  $”FE00 027F F8F8 F500 08FE 0002 FEF8 F8F5"
  $”0011 0900 0001 F878 F001 E000 3FFD 0000"
  $”7FFE 0013 0F00 0001 F0F8 FFC1 FFC0 FF87"
  $”FE00 01FF E0FF 0013 0F00 0003 E0F9 FFE1"
  $”FFE1 FFC7 FF7E 03FF E0FF 0013 0F00 0003"
  $”E0F1 FFF0 FFE3 FFC7 FFFF 07F3 E0FF 0013"
  $”0F00 0003 C001 FFF0 FDE7 E3C7 EFFF 8FC3"
  $”E0FF 0013 0F00 0003 C001 FCF0 F807 C3C7"
  $”C7FF 8F83 C0FF 0013 0F00 0003 C001 FCF1"
  $”F00F 83C7 C7E7 9F07 C0FF 0013 0F00 0003"
  $”C001 F8F1 F00F 83CF 87C7 9F07 C0FF 0013"
  $”0F00 0003 C001 F8F1 E00F 03CF 8F87 9E0F”
  $”80FF 0013 0F00 0003 C001 F9F1 E00F 07CF”
  $”0F87 9E0F 80FF 0013 0F00 0003 E001 F1F3"
  $”E00F 07CF 0F07 9E1F 80FF 0013 0F00 0003"
  $”E0F1 F1E3 E00F 0F9F 0F0F 9F3F 80FF 0013"
  $”0F00 0001 F9F1 F3E3 C00F BF9F 1F0F 9FFF”
  $”80FF 0013 0F00 0001 FFF1 E3E3 C00F FF1E”
  $”1F0F 0FFF C0FF 0012 FE00 0CFF E1E3 C3C0"
  $”07FE 1E1E 0F0F FFC0 FF00 12FE 000C 3FC1"
  $”E3C3 C003 F81E 1E0F 07E3 C0FF 0002 EF00"
  $”02EF 0002 EF00 02EF 0002 EF00 0901 0003"
  $”FA00 0018 F900 1305 0003 0000 0380 FE00"
  $”0838 C000 0006 0030 6000 1104 0006 0000"
  $”0EFD 0001 39C0 FD00 0230 6000 1311 0007"
  $”C630 180F CF07 007B C3E7 EFCC 39FB F000"
  $”1311 0007 6630 300E 198D 807E C667 0E0C”
  $”6C60 C000 1311 0006 3660 338C 3199 80DE”
  $”CC66 0C0C CC60 C000 1311 0006 33C0 36CC”
  $”3F19 80DD 98C6 0C0D 8C60 C000 1311 000C”
  $”33C0 30D8 3033 80D9 98CC 1819 8CC1 8000"
  $”1311 000C 6180 1998 3337 8183 19CC 1819"
  $”98C1 8000 1311 000F C180 0F18 1E1F 0183"
  $”0FCC 1818 F0C1 8000 0A02 0000 03FD 0000"
  $”03F7 000A 0200 0003 FD00 0036 F700 0A02"
  $”0000 06FD 0000 1CF7 0002 EF00 02EF 0002"
  $”EF00 02EF 0002 EF00 02EF 0002 EF00 02EF”
  $”0002 EF00 02EF 0002 EF00 02EF 0002 EF00"
  $”02EF 0005 0100 3CF1 0012 0E00 4210 E38E”
  $”0FA0 0104 0044 003C 41C0 FE00 120E 0099"
  $”3114 5102 2001 8C00 4400 16C2 20FE 0013"
  $”1100 A111 1451 0238 C154 C644 C895 420B”
  $”325C 0013 1100 A110 F38E 0225 2124 297C”
  $”2514 426C 4A52 0013 1100 9910 1451 0225"
  $”E104 E844 E200 0228 4A52 0013 1100 4210"
  $”2451 0225 0105 2945 2500 0228 4A52 0013"
  $”1100 3C10 C38E 0224 C104 E644 E880 01C8"
  $”31DC 0005 F100 0110 0005 F100 0110 0002"
  $”EF00 02EF 0002 EF00 10FE 0006 046C 3C40"
  $”8200 78FD 0000 40FE 0010 FE00 0604 2422"
  $”0082 0044 FD00 0040 FE00 11FE 000B 0A24"
  $”22CE E738 44C7 32D1 31C0 FE00 11FE 000B”
  $”0A24 3C52 9240 7928 4B0A 4A40 FE00 11FE”
  $”000B 1F24 2852 9230 51E6 7A0A 7A40 FE00"
  $”11FE 000B 1124 2452 9208 4901 4204 4240"
  $”FE00 11FE 000B 1124 224E 9170 44CE 3204"
  $”31C8 FE00 06FB 0000 02F6 0006 FB00 000C”
  $”F600 02EF 0002 EF00 02EF 0002 EF00 02EF”
  $”00A0 0083 FF”
};

resource ‘PICT’ ( ( 0xC000 | ( DriverID << 5 ) ) +
                  sorryPicture ) {
  521,
  {328, 367, 366, 461},
  $”1101 A000 8201 000A 0000 0000 02D0 0240"
  $”9800 0E01 4801 6801 6E01 D001 4801 6F01"
  $”6E01 CD01 4801 6F01 6E01 CD00 000F 0600"
  $”3C07 0000 C070 FE00 030C 00C0 000F 0600"
  $”1803 0000 CC30 FE00 030C 00C0 000D 0600"
  $”1803 0000 CC30 FC00 01C0 000F 0B00 181F”
  $”3DF8 1E3E 783E F3DD F8FF 000F 0B00 1833"
  $”66EC 0C3B CC67 9E6C ECFF 000F 0B00 1833"
  $”66CC 0C33 FC79 FFEC CCFF 000F 0B00 1833"
  $”66CC 0C33 C01F 860C CCFF 000F 0B00 1837"
  $”66CC 0C33 CC67 9E6C CCFF 000F 0B00 3C1F”
  $”BDFE 073E 787C F3DF FEFF 0002 F300 02F3"
  $”0002 F300 02F3 000B FC00 001C FE00 01E1"
  $”C0FE 000B FC00 050C 0001 8060 C0FE 000B”
  $”FC00 050C 0001 8060 C0FE 000F 0B00 03F1"
  $”E0F3 CCF7 E3DE 7CCF 3EFF 000F 0B00 01DB”
  $”319E 6D9B E1B3 76D9 E6FF 000F 0B00 019B”
  $”3186 6D9B 018F 66DF F8FF 000F 0B00 019B”
  $”3186 6D9B 01BB 66D8 1EFF 000F 0B00 019B”
  $”319E 6D9B 01B7 66D9 E6FF 000F 0B00 03FD”
  $”E0F3 DEF7 80FF FDEF 7CFF 0002 F300 02F3"
  $”0002 F300 02F3 000C 0800 0001 CC00 0E00"
  $”00E0 FC00 0C08 00C0 00CC 0006 0000 60FC”
  $”000C 0800 C000 C000 0600 0060 FC00 0F0B”
  $”01EF 07DC FFE6 7BFC 7C7B F780 FF00 0F0B”
  $”00D9 8CCD 9BB6 CD98 76CD FCC0 FF00 0F0B”
  $”00D9 8CCD E336 3D98 66FD 8FC0 FF00 0E0A”
  $”00D9 8CCC 7B36 ECF0 66C1 8CFE 000F 0D00"
  $”D98D CD9B 36DC F066 CD8C D998 000F 0D00"
  $”7F07 FFF3 EF7E 60FF 7BC7 9998 0009 FD00"
  $”0303 0000 60FB 0009 FD00 0303 0003 C0FB”
  $”0009 FD00 0307 8003 80FB 00A0 0083 FF”
};

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Latest Forum Discussions

See All

Go from lowly lizard to wicked Wyvern in...
Do you like questing, and do you like dragons? If not then boy is this not the announcement for you, as Loongcheer Game has unveiled Quest Dragon: Idle Mobile Game. Yes, it is amazing Square Enix hasn’t sued them for copyright infringement, but... | Read more »
Aether Gazer unveils Chapter 16 of its m...
After a bit of maintenance, Aether Gazer has released Chapter 16 of its main storyline, titled Night Parade of the Beasts. This big update brings a new character, a special outfit, some special limited-time events, and, of course, an engaging... | Read more »
Challenge those pesky wyverns to a dance...
After recently having you do battle against your foes by wildly flailing Hello Kitty and friends at them, GungHo Online has whipped out another surprising collaboration for Puzzle & Dragons. It is now time to beat your opponents by cha-cha... | Read more »
Pack a magnifying glass and practice you...
Somehow it has already been a year since Torchlight: Infinite launched, and XD Games is celebrating by blending in what sounds like a truly fantastic new update. Fans of Cthulhu rejoice, as Whispering Mist brings some horror elements, and tests... | Read more »
Summon your guild and prepare for war in...
Netmarble is making some pretty big moves with their latest update for Seven Knights Idle Adventure, with a bunch of interesting additions. Two new heroes enter the battle, there are events and bosses abound, and perhaps most interesting, a huge... | Read more »
Make the passage of time your plaything...
While some of us are still waiting for a chance to get our hands on Ash Prime - yes, don’t remind me I could currently buy him this month I’m barely hanging on - Digital Extremes has announced its next anticipated Prime Form for Warframe. Starting... | Read more »
If you can find it and fit through the d...
The holy trinity of amazing company names have come together, to release their equally amazing and adorable mobile game, Hamster Inn. Published by HyperBeard Games, and co-developed by Mum Not Proud and Little Sasquatch Studios, it's time to... | Read more »
Amikin Survival opens for pre-orders on...
Join me on the wonderful trip down the inspiration rabbit hole; much as Palworld seemingly “borrowed” many aspects from the hit Pokemon franchise, it is time for the heavily armed animal survival to also spawn some illegitimate children as Helio... | Read more »
PUBG Mobile teams up with global phenome...
Since launching in 2019, SpyxFamily has exploded to damn near catastrophic popularity, so it was only a matter of time before a mobile game snapped up a collaboration. Enter PUBG Mobile. Until May 12th, players will be able to collect a host of... | Read more »
Embark into the frozen tundra of certain...
Chucklefish, developers of hit action-adventure sandbox game Starbound and owner of one of the cutest logos in gaming, has released their roguelike deck-builder Wildfrost. Created alongside developers Gaziter and Deadpan Games, Wildfrost will... | Read more »

Price Scanner via MacPrices.net

13-inch M2 MacBook Airs in stock today at App...
Apple has 13″ M2 MacBook Airs available for only $849 today in their Certified Refurbished store. These are the cheapest M2-powered MacBooks for sale at Apple. Apple’s one-year warranty is included,... Read more
New today at Apple: Series 9 Watches availabl...
Apple is now offering Certified Refurbished Apple Watch Series 9 models on their online store for up to $80 off MSRP, starting at $339. Each Watch includes Apple’s standard one-year warranty, a new... Read more
The latest Apple iPhone deals from wireless c...
We’ve updated our iPhone Price Tracker with the latest carrier deals on Apple’s iPhone 15 family of smartphones as well as previous models including the iPhone 14, 13, 12, 11, and SE. Use our price... Read more
Boost Mobile will sell you an iPhone 11 for $...
Boost Mobile, an MVNO using AT&T and T-Mobile’s networks, is offering an iPhone 11 for $149.99 when purchased with their $40 Unlimited service plan (12GB of premium data). No trade-in is required... Read more
Free iPhone 15 plus Unlimited service for $60...
Boost Infinite, part of MVNO Boost Mobile using AT&T and T-Mobile’s networks, is offering a free 128GB iPhone 15 for $60 per month including their Unlimited service plan (30GB of premium data).... Read more
$300 off any new iPhone with service at Red P...
Red Pocket Mobile has new Apple iPhones on sale for $300 off MSRP when you switch and open up a new line of service. Red Pocket Mobile is a nationwide MVNO using all the major wireless carrier... Read more
Clearance 13-inch M1 MacBook Airs available a...
Apple has clearance 13″ M1 MacBook Airs, Certified Refurbished, available for $759 for 8-Core CPU/7-Core GPU/256GB models and $929 for 8-Core CPU/8-Core GPU/512GB models. Apple’s one-year warranty is... Read more
Updated Apple MacBook Price Trackers
Our Apple award-winning MacBook Price Trackers are continually updated with the latest information on prices, bundles, and availability for 16″ and 14″ MacBook Pros along with 13″ and 15″ MacBook... Read more
Every model of Apple’s 13-inch M3 MacBook Air...
Best Buy has Apple 13″ MacBook Airs with M3 CPUs in stock and on sale today for $100 off MSRP. Prices start at $999. Their prices are the lowest currently available for new 13″ M3 MacBook Airs among... Read more
Sunday Sale: Apple iPad Magic Keyboards for 1...
Walmart has Apple Magic Keyboards for 12.9″ iPad Pros, in Black, on sale for $150 off MSRP on their online store. Sale price for online orders only, in-store price may vary. Order online and choose... Read more

Jobs Board

Solutions Engineer - *Apple* - SHI (United...
**Job Summary** An Apple Solution Engineer's primary role is tosupport SHI customers in their efforts to select, deploy, and manage Apple operating systems and Read more
DMR Technician - *Apple* /iOS Systems - Haml...
…relevant point-of-need technology self-help aids are available as appropriate. ** Apple Systems Administration** **:** Develops solutions for supporting, deploying, 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
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
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
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.