TweetFollow Us on Twitter

Reminder DA
Volume Number:4
Issue Number:3
Column Tag:Forth Forum

Time Manager Reminder DA

By Jörg Langowski, MacTutor Editorial Board, Grenoble, France

Jörg Langowski is a bio-chemical engineer for a french concern and is a founding and current board member of MacTutor. He can be reached at EMBL, c/o I.L.L. 156x, Grenoble, Cedex, France F-38042. We encourage European authors to contact Jörg directly about submissions to MacTutor.

“Using the Time Manager”

One thing I always wanted to have on my Mac is some utility that reminds me of an appointment, no matter what I’m doing on the machine at any given time. On our VAX, for example, there is this great program called Reminder which sits in the background and will beep at you when your next appointment arrives.

In the new system (128K ROMs and up) there exists a set of routines called the Time Manager. I thought it would be a good idea to show you their usage in developing a Reminder utility similar to the one on the VAX. In the process, I’ll show you how to work with modeless dialogs from a DA, how to call memory manager dependent traps from a time manager task, and some more.

The Time Manager

The Time manager is used to execute a task at a predetermined time. Its routines are documented in IM Vol. 4. All time manager tasks are described by entries in the time mamager queue, where each element has the following format:

header TMtask 14 allot
0 CONSTANT qLink
4 CONSTANT qType
6 CONSTANT tmTask
10 CONSTANT tmCount

That means, the queue entry looks just like a regular queue element, with two 4-byte fields, tmTask and tmCount, relevant to our task. tmTask contains a pointer to the routine to be executed, and tmCount is used by the system to count down the elapsed time. When it has reached zero, the task at tmTask will be executed.\

Three routines are provided by the time manager: InsTime, called with a pointer to the queue element in A0, will insert this queue element into the time manager queue. PrimeTime, with the queue element pointer in A0 and a 32-bit count in D0, will schedule the routine specified in that queue element to be executed after count milliseconds have elapsed. RmvTime, with a pointer to the queue element in A0, will remove the queue element. The Mach2 interface to these routines is given at the beginning of listing 1.

Fig. 1 Our Reminder DA lets Mac Widows post alerts for late night programmers!

Programming the Reminder utility

The strategy to follow seems very simple: we create a desk accessory that allows us to enter a message text and a delay time, that desk accessory will then setup a queue element with a pointer to a routine that displays an alert box containing that string.

Thinking about it, programming such a utility is not quite so simple. First of all, the routine passed to the time manager for execution cannot be part of the desk accessory. We’d like to enter appointments that are due in several hours or days (32 bits of milliseconds, unsigned, give a maximum possible delay of 49.7 days), and we’ll most probably have left the application where the desk accessory was started by then. Under MultiFinder this doesn’t matter, but under Finder, the desk accessory would have been closed, leaving the task pointer point to anything but the desired code.

My first thought was to use a ‘stick-around’ desk accessory that would automatically restart itself after an involuntary close, like I described earlier. But it is actually much easier to put a copy of the routine to be executed into a small block of system heap, leaving it independent of the DA. Then, one has to take caution that the routine, once executed, will remove its own queue entry and dispose of its own memory.

The second problem is that a time manager task may be executed at any time, interrupting whatever else is being done at that moment. For the same reason as in the case of VBL tasks, we may not call any routines from the time manager task that can move things around in the heap. If we did, there would be a chance that the interrupt occurs right in the middle of a memory manager operation, or while a handle hangs around dereferenced somewhere.

The time manager task must therefore be rather simple. I use the same trick as I described for the ‘stick-around’ DA, patching SystemTask from the scheduled routine. The next time SystemTask is called (which should happen rather soon in any benign application) the patch routine will be executed, which then can do the more involved stuff such as drawing an alert box.

Now look at the first part of the example: the routine that is executed by the time manager is contained between the markers mytask and mytask.end. The first bytes of this block contain the queue element. The name string ‘Reminder’ follows for debugging purposes. Some local variable space is reserved, where the original SystemTask trap address, the alert ID and the alert message can be kept. The SystemTask patch routine alertMe follows. It will display a note alert with the message in parameter ^0, unlock the alert, remove the time manager queue element and dispose of the memory allocated for itself.

Fig.2 After time has elapsed, an alert pops up!

alertMe is patched into SystemTask by the following routine, wakeMe, which is the one first executed by the time manager. A pointer to wakeMe will be contained in the tmTask field of the queue element at the beginning of the block. Since we do not know yet where this routine will be located, we’ll have to install the pointer after moving the code into the system heap.

As you see, the code between mytask and mytask.end is completely self-contained (as long as the ALRT resource can be found). We may therefore move any number of these little code blocks into the system heap and install their queue elements using the time manager; each will be executed at its scheduled time and display its little message. Appointment ‘objects’, so to say.

The desk accessory

The DA is used to install the tasks. It is a very simple DA which just draws up a modeless dialog box with two editable text items. The dialog window will have the driver reference number in its windowKind field, so that the system will handle mouse down events in the close box and drag region. Only when the event is passed through to the DA, windowKind will be temporarily set to 2 (dialog window), so that IsDialogEvent and DialogSelect work correctly.

When the OK button in the dialog box has been clicked, the dialog handler will be invoked. This routine converts the string in item 4 to a number, the delay in seconds, and gets the message to be displayed after this delay (item 3). These parameters are passed to install.wakeup, together with the alert ID. install.wakeup gets the wakeup routine described above from the resource file and installs a copy of it in the system heap. It saves a pointer to the wakeup routine in the tmTask field of the queue element, stores the alert ID and the message string at their appropriate positions and then schedules the routine for execution by calling InsTime and PrimeTime.

Things missing

The desk accessory described here is already quite useful ‘as is’. However, one could include some improvements that I leave as an exercise for you (or me, for that matter):

- Input of the appointment time in standard date format.

- Keeping a list of appointments that can be displayed and edited.

- Saving this list to a file every time it is changed; this file is then checked on system startup and the pending appointments rescheduled automatically.

I wish you good luck with those experiments; now, some mail that I recently received.

Feedback Dept.

“Dear Jörg,

I read your recent column in MacTutor with great interest and would like to obtain the addresses for Serge Rostan and also for Winsoft. [Serge Rostan, “TechnoPro”, rue Faraday, F-78180 Montigny le Bretonneux, France, phone (33) 1 30 45 26 62, and Winsoft, 34, boulevard de l’Esplanade, F-38000 Grenoble, France, phone (33) 76 87 56 01 - JL].

We are in the process of completing a book on fonts for the Macintosh for European and many other non-Roman languages. It will also show specimens of over 2000 bit-mapped and several hundred PostScript fonts.

If you can suggest any font vendors that do not advertise in US Macintosh magazines, it would be very helpful [not off the top of my head, but I’ll look around - JL].

As you may know, Apple refuses to sell European keyboards in the US, even to certified developers. Users here must cultivate acquaintances overseas and buy them indirectly. Do you know whether Apple tries to prevent the export of such keyboards from Europe? We would like to be able to list a commercial source for such keyboards in our book, but do not want to cause difficulties for anyone there. If they are readily available for export, we would appreciate the name of a recommended source.

[You address a problem that I’ve encountered myself. There seems no way for Macintosh developers in France to get other than French keyboards through the developer program. However, there is at least one Apple dealer in Grenoble who sells the US keyboard on request; we have several international research institutions here, so there’s a market. I’ll send you addresses of some Apple dealers in Germany and France that you might be able to order from.

I don’t think there are any export restrictions imposed by Apple on non-US keyboards into the US (unless you re-sell them to Colonel Kh...). The problem most probably is the bureaucracy that inevitably builds up in a large corporation, even one like Apple that for a while tried to maintain some ‘non-conformistic hacker’ kind of image. Which it is trying to forget at a rapid rate, I presume. Someone, it seems, must have set a guideline that in country X only systems localized for X will be sold, with few exceptions. The only way I get the most recent US system updates is through US sources, too. Funniest of all: The MacII system that I finally got a week ago (yes, I love it), has English documentation, US system disks (but 4.1, not 4.2, which is not officially released at the time I write this), but no way can I get a US keyboard. Probably the people at Apple France just wanted to be nice and ship me as many US parts as possible, but then they had only French keyboards. What a nuisance to have all the numbers on the top row...]

Lastly, Apple also tries to limit the availability of any Script Manager code or fonts it has developed to the country for which it was developed! This seems strange given that the Macintosh is touted as a Multinational machine. Apple has made Kanji and Arabic available through APDA, but feels that they are sufficient for the testing purposes intended. They have also developed a Chinese, a Hebrew and a Greek. The Chinese is distributed from Hong Kong and the Hebrew and Greek are distributed from Paris. I have written to the Paris office to no avail after a conversation with Mark Davis at Apple, the creator of the Script Manager. Do you know of a way for someone in the US to get these fonts from Paris? Actually, I am more interested in finding out the arrangement of characters in the coding table than I am in the font, but the exact status of ‘dead’ keys might be hard to discern accurately without actually having the font in hand.

Best regards,

Tim Ryan, SourceNet, Santa Barbara, CA “

[You address a very timely issue, that’s why I have your letter printed immediately without having the answers on hand yet. I’ll forward your mail with my comments to Apple France. I’m actually quite optimistic that you can get the Script Manager versions that you want. JL]

One comment to the letter from Peter Adamson, MT V4#1, p.11: The Pascal equivalent to the Mach2 PAUSE is actually WaitNextEvent; much like PAUSE under Mach2, WaitNextEvent will transfer control to the next MultiFinder task under certain circumstances. If you have a very long event loop, you may try to intersperse WaitNextEvents with event masks of zero, so that they’ll always return a null event. That should transfer control to the next task under MultiFinder. Only the crucial WaitNextEvent - the one with the BIG case statement behind it - would be called with a non-zero event mask. This is all untested, so don’t blame me if it doesn’t work.

See you next month.

Listing 1: Appointment reminder using the time manager
\ ***** Time manager example - a ‘reminder’ utility
\ J. Langowski December 87 
\
\ Strategy: write a driver that sets up a dialog which allows 
\ to enter a time & message to display after that time. After 
\ the appointment has been entered, the driver sets up a 
\ time manager call for that appointment.
\ The time manager routine installs a SystemTask trap 
\ patch which at the next occasion will draw an alert box 
\ containing the message to be displayed. 
\
\ Note that we have to use the patch rather than calling 
\ the alert routine directly from our time manager task,
\ since we can’t be sure we’re not in the middle of a 
\ memory manager operation when it is called.
\

only forth also assembler also mac

CODE InsTime ( tmTaskPtr | -- )
 MOVE.L (A6)+,A0
 _InsTime
 RTS
END-CODE MACH

CODE PrimeTime ( tmTaskPtr count | -- )
 MOVE.L (A6)+,D0
 MOVE.L (A6)+,A0
 _PrimeTime
 RTS
END-CODE MACH

CODE RmvTime ( tmTaskPtr | -- )
 MOVE.L (A6)+,A0
 _RmvTime
 RTS
END-CODE MACH

4ascii MENU constant “menu
4ascii PROC constant “proc

\ *** compiler support words for external definitions *** 
: :xdef 
 create -4 allot
 $4EFA w, ( JMP )
 0 w,  ( entry point to be filled later )
 0 ,   ( length of routine to be filled later )
 here 6 - 76543
;

: ;xdef { branch marker entry | -- }
 marker 76543 <> abort” xdef mismatch”
 entry branch - branch w!
 here branch - 2+ branch 2+ !
; 
 
: xlen 4 + @ ; ( get length word of external definition )

( *** driver header block *** )

 0 CONSTANT drvrFlags
 2 CONSTANT drvrdelay 
 4 CONSTANT drvrEMask
 6 CONSTANT drvrMenu
 8 CONSTANT drvrOpen
10 CONSTANT drvrPrime
12 CONSTANT drvrCtl
14 CONSTANT drvrStatus
16 CONSTANT drvrClose
18 CONSTANT drvrname
50 CONSTANT DAlength

\ *** compiler support words for DA and driver definitions 
: :DA 
 create -4 allot
 here 87654 ( start of DA block, and marker )
 50 allot   ( length of block )
;

: ;DA { DAstart marker Ropen Rprime Rctl Rstatus Rclose
 Rflags Rdelay Remask Rmenu Rname | -- }
 marker 87654 <> abort” DA definition mismatch”
 Ropen  DAStart - DAStart drvrOpen + w!
 Rprime DAStart - DAStart drvrPrime + w!
 Rctl   DAStart - DAStart drvrCtl + w!
 Rstatus  DAStart - DAStart drvrStatus + w!
 Rclose DAStart - DAStart drvrClose + w!
 Rflags DAStart drvrFlags + w!
 Rdelay DAStart drvrDelay + w!
 Remask DAStart drvrEmask + w!
 RMenu  DAStart drvrMenu + w!
 Rname count dup DAStart drvrName + c!
 DAStart drvrName + 1+ swap 
 dup 31 > if drop 31 then cmove 
 here DAstart -    DAStart DAlength + !
; 
 
: DAlen DAlength + @ ;
\ get length word of external definition

\ **** DA glue macros

CODE DA.prelude
 LINK A6,#-512 \ 512 bytes of local Forth stack
 MOVEM.L A0-A1,-(A7) \ save registers
 MOVE.L  A6,A3 \ setup local loop return stack
 SUBA.L   #256,A3  \ in the low 256 local stack bytes
 MOVE.L  A0,-(A6)  \ parameter block
 MOVE.L  A1,-(A6)\ device control entry
 RTS  \ just to indicate the MACHro stops here 
END-CODE MACH

CODE DA.epilogue
 MOVE.L  (A6)+,D0\ return code
 MOVEM.L (A7)+,A0-A1 \ restore registers
 UNLK A6
 RTS
END-CODE MACH

CODE DA.Jiodone
 MOVE.L  (A6)+,D0\ return code
 MOVEM.L (A7)+,A0-A1 \ restore registers
 UNLK A6
 move.l JIODone,A0
 movem.l d4-d7/a4-a6,-(a7)
 jsr    (a0)
 movem.l(a7)+,d4-d7/a4-a6
 RTS
END-CODE MACH

.TRAP _newptr,sys$A51E

%0000000101001010 CONSTANT DAEmask

$1B4 CONSTANT SystemTask

\ ____________________________________________
\ time manager and systemTask patch routine
\ this routine must reside in a block allocated 
\ in the system heap through a pointer. 
\ ____________________________________________

header myTask 14 allot
6 CONSTANT taskPtr
HEADER myName
 DC.B   9,0,’Reminder’
header myTrap 4 allot
header myAlert 4 allot
header myString 256 allot

: alertMe 
 MOVEM.LA0-A4/A6/D0-D7,-(A7)
 LINK A6,#-128 \ 128 bytes of local Forth stack
 (call) frontwindow windowkind + @
 2 <> IF
 [‘] myTrap @ SystemTask (call) SetTrapAddress
 [‘] myString 0 0 0 (call) paramText
 [‘] myAlert @ 0 (call) noteAlert drop
 [‘] myAlert @ (call) freeAlert
 [‘] myTask RmvTime
 [‘] myTask (call) DisposPtr drop
 THEN
 UNLK A6
 MOVEM.L(A7)+,A0-A4/A6/D0-D7
;

: wakeMe
 SystemTask (call) GetTrapAddr [‘] myTrap !
 [‘] alertMe SystemTask (call) SetTrapAddr
;

header mytask.end
‘ wakeme ‘ mytask - CONSTANT *wakeme \ task offset
‘ myAlert ‘ mytask - CONSTANT *myAlert \ alertID 
‘ myString ‘ mytask - CONSTANT *myString \ alert string

\ ___________________________________________
\ desk accessory code starts here.
\ ___________________________________________

:DA reminder 
 .ALIGN

( *** main desk accessory routines *** )
header myRes0 4 allot\ local res ID=0 offset 
header dlgText 256 allot

\ redefinition of cmove to make it 
\ available locally

CODE cmove
 move.l (a6)+,d0
 move.l (a6)+,a1
 move.l (a6)+,a0
 tst.l  d0
 ble.s  @2
@1 move.b (a0)+,(a1)+
 subq.l #1,d0
 bne.s  @1
@2 rts
END-CODE

\ ___________________
\ wakeup routine installation
\ ___________________

: install.wakeup 
 { delay alrtID msg | procHdl hSize taskBlock -- }
 
 “proc [‘] myRes0 @ (call) GetResource -> procHdl
 procHdl (call) getHandleSize -> hSize
 hSize MOVE.L (A6)+,D0
 _newPtr,sys
 MOVE.L A0,-(A6) -> taskBlock
 procHdl @ taskBlock hSize cmove
 procHdl (call) releaseResource
   \ we have made a local copy of the wakeup routine
 taskBlock dup *wakeMe + swap taskPtr + !
 msg taskBlock *myString + 256 cmove
 alrtID taskBlock *myAlert + !
 alrtID (call) CouldAlert
 taskBlock InsTime
 taskBlock delay PrimeTime
 \ now the wakeup routine will wake up after
 \ the scheduled delay.
;

: getDrvrID { dCtlEntry | -- num }
 dCtlEntry dCtlRefNum + w@ l_ext
 1+ negate
;

: ownResID ( resID drvrID )
 5 shl + -16384 +
;
: Open { parblk dce | DAWind Res0 -- returncode }
 5 (call) sysbeep 
 \ to get attention if automatically opened
 0 dce getDrvrID ownResID -> Res0
 dce dCtlWindow + @ -> DAWind
 DAWind 0= IF ( not open already )
 Res0 [‘] myRes0 !
 Res0 0 -1 (call) getNewDialog -> DAWind
 DAWind  dce dCtlWindow + !  
 \ store dialog pointer
 DAWind  dce dCtlRefNum + w@  
 swap windowKind + w!
 ELSE
 DAWind (call) selectWindow
 THEN
 0
;
: Close { parblk dce | -- returncode }
 dce dCtlWindow + 
 dup @ (call) DisposDialog  
 0 swap ! ( so that Open will work again )
 0
;
: dialog-handler 
 { dlgPtr itemHit | 
 itemType hItem rBox seconds -- }

\ we get here if the OK button in the dialog
\ has been hit, therefore itemHit is always =1 
\ - in our case. But it is nice to have itemHit
\ available, to be more general. 
\ item #3 contains the appointment message
\ item #4 contains the delay in seconds
\ (decimal number string)

 dlgPtr 4 ^ itemType ^ hItem ^ rBox (call) GetDItem
 hItem [‘] dlgText (call) GetIText
 [‘] dlgText (call) StringToNum -> seconds
 seconds 0> IF
 dlgPtr 3 ^ itemType ^ hItem ^ rBox 
 (call) GetDItem
 hItem [‘] dlgText (call) GetIText
 seconds 1000 w* 
 [‘] myres0 @ [‘] dlgText install.wakeup
 ELSE 10 (call) sysbeep
 THEN
;

: Ctl { parblk dce | 
 DAWind event-rec dlgPtr itemHit -- returncode }
 dce dCtlWindow + @ -> DAWind

 parblk csCode + w@ l_ext 
 CASE
 accEvent OF
 2 DAWind windowKind + w! 
 \ set to dialog window 
 parblk csParam + @ -> event-rec
 event-rec (call) IsDialogEvent
 IF  event-rec ^ dlgPtr ^ itemHit
 (call) Dialogselect
 IF dlgPtr itemHit dialog-handler THEN
 THEN
 DAWind  dce dCtlRefNum + w@  
 swap windowKind + w! 
 \ reset windowkind
 ENDOF

 ENDCASE
 0
;
: DrOpen DA.Prelude Open DA.Epilogue ;
: DrClose DA.Prelude Close DA.Epilogue ;
: DrCtl DA.Prelude Ctl DA.JioDone ;
: DrStatus ;
: DrPrime ;

‘ DrOpen ‘ DrPrime ‘ DrCtl ‘ DrStatus ‘ DrClose
$7400 \ need lock, need time, need goodbye, ctl calls
60 DAEmask 0 \ delay mask menu
“ Reminder” \ name
;DA


( write resource to file ) 
: $create-res ( str-addr - errcode )
 call CreateResFile
 call ResError L_ext
;
: $open-res { addr | refNum - refNum or errcode }
 addr call OpenResFile -> refNum
 call ResError L_ext
 ?dup IF ELSE refNum THEN
; 
: close-res ( refNum - errcode )
 call CloseResFile
 call ResError L_ext
;
: make-res { addr len rtype ID name | -- }
 addr len call PtrToHand 
 abort” Could not create resource handle”
 rtype ID name call AddResource
;
: write-out { filename | refnum -- } 
 filename $create-res 
 abort” That resource file already exists”
 filename $open-res
 dup 0< abort” Open resource file failed”
 -> refnum
 refnum call UseResFile
 [‘] reminder dup DALen
 “drvr 12 “ Reminder” make-res
 [‘] myTask [‘] mytask.end over - 
 “proc -16000 “ wakeUp” make-res
 “proc -16000 call GetResource
 dup 80 call SetResAttrs  
 ( 64: sysheap + 16: locked )
 call ChangedResource
 refnum close-res 
 abort” Could not close resource file”
;
: make-DA
 “ Reminder.rsrc” $delete drop
 “ Reminder.rsrc” write-out
;
 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Latest Forum Discussions

See All

Tokkun Studio unveils alpha trailer for...
We are back on the MMORPG news train, and this time it comes from the sort of international developers Tokkun Studio. They are based in France and Japan, so it counts. Anyway, semantics aside, they have released an alpha trailer for the upcoming... | Read more »
Win a host of exclusive in-game Honor of...
To celebrate its latest Jujutsu Kaisen crossover event, Honor of Kings is offering a bounty of login and achievement rewards kicking off the holiday season early. [Read more] | Read more »
Miraibo GO comes out swinging hard as it...
Having just launched what feels like yesterday, Dreamcube Studio is wasting no time adding events to their open-world survival Miraibo GO. Abyssal Souls arrives relatively in time for the spooky season and brings with it horrifying new partners to... | Read more »
Ditch the heavy binders and high price t...
As fun as the real-world equivalent and the very old Game Boy version are, the Pokemon Trading Card games have historically been received poorly on mobile. It is a very strange and confusing trend, but one that The Pokemon Company is determined to... | Read more »
Peace amongst mobile gamers is now shatt...
Some of the crazy folk tales from gaming have undoubtedly come from the EVE universe. Stories of spying, betrayal, and epic battles have entered history, and now the franchise expands as CCP Games launches EVE Galaxy Conquest, a free-to-play 4x... | Read more »
Lord of Nazarick, the turn-based RPG bas...
Crunchyroll and A PLUS JAPAN have just confirmed that Lord of Nazarick, their turn-based RPG based on the popular OVERLORD anime, is now available for iOS and Android. Starting today at 2PM CET, fans can download the game from Google Play and the... | Read more »
Digital Extremes' recent Devstream...
If you are anything like me you are impatiently waiting for Warframe: 1999 whilst simultaneously cursing the fact Excalibur Prime is permanently Vault locked. To keep us fed during our wait, Digital Extremes hosted a Double Devstream to dish out a... | Read more »
The Frozen Canvas adds a splash of colou...
It is time to grab your gloves and layer up, as Torchlight: Infinite is diving into the frozen tundra in its sixth season. The Frozen Canvas is a colourful new update that brings a stylish flair to the Netherrealm and puts creativity in the... | Read more »
Back When AOL WAS the Internet – The Tou...
In Episode 606 of The TouchArcade Show we kick things off talking about my plans for this weekend, which has resulted in this week’s show being a bit shorter than normal. We also go over some more updates on our Patreon situation, which has been... | Read more »
Creative Assembly's latest mobile p...
The Total War series has been slowly trickling onto mobile, which is a fantastic thing because most, if not all, of them are incredibly great fun. Creative Assembly's latest to get the Feral Interactive treatment into portable form is Total War:... | Read more »

Price Scanner via MacPrices.net

Early Black Friday Deal: Apple’s newly upgrad...
Amazon has Apple 13″ MacBook Airs with M2 CPUs and 16GB of RAM on early Black Friday sale for $200 off MSRP, only $799. Their prices are the lowest currently available for these newly upgraded 13″ M2... Read more
13-inch 8GB M2 MacBook Airs for $749, $250 of...
Best Buy has Apple 13″ MacBook Airs with M2 CPUs and 8GB of RAM in stock and on sale on their online store for $250 off MSRP. Prices start at $749. Their prices are the lowest currently available for... Read more
Amazon is offering an early Black Friday $100...
Amazon is offering early Black Friday discounts on Apple’s new 2024 WiFi iPad minis ranging up to $100 off MSRP, each with free shipping. These are the lowest prices available for new minis anywhere... Read more
Price Drop! Clearance 14-inch M3 MacBook Pros...
Best Buy is offering a $500 discount on clearance 14″ M3 MacBook Pros on their online store this week with prices available starting at only $1099. Prices valid for online orders only, in-store... Read more
Apple AirPods Pro with USB-C on early Black F...
A couple of Apple retailers are offering $70 (28%) discounts on Apple’s AirPods Pro with USB-C (and hearing aid capabilities) this weekend. These are early AirPods Black Friday discounts if you’re... Read more
Price drop! 13-inch M3 MacBook Airs now avail...
With yesterday’s across-the-board MacBook Air upgrade to 16GB of RAM standard, Apple has dropped prices on clearance 13″ 8GB M3 MacBook Airs, Certified Refurbished, to a new low starting at only $829... Read more
Price drop! Apple 15-inch M3 MacBook Airs now...
With yesterday’s release of 15-inch M3 MacBook Airs with 16GB of RAM standard, Apple has dropped prices on clearance Certified Refurbished 15″ 8GB M3 MacBook Airs to a new low starting at only $999.... Read more
Apple has clearance 15-inch M2 MacBook Airs a...
Apple has clearance, Certified Refurbished, 15″ M2 MacBook Airs now available starting at $929 and ranging up to $410 off original MSRP. These are the cheapest 15″ MacBook Airs for sale today at... Read more
Apple drops prices on 13-inch M2 MacBook Airs...
Apple has dropped prices on 13″ M2 MacBook Airs to a new low of only $749 in their Certified Refurbished store. These are the cheapest M2-powered MacBooks for sale at Apple. Apple’s one-year warranty... Read more
Clearance 13-inch M1 MacBook Airs available a...
Apple has clearance 13″ M1 MacBook Airs, Certified Refurbished, now available for $679 for 8-Core CPU/7-Core GPU/256GB models. Apple’s one-year warranty is included, shipping is free, and each... Read more

Jobs Board

Seasonal Cashier - *Apple* Blossom Mall - J...
Seasonal Cashier - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Seasonal Fine Jewelry Commission Associate -...
…Fine Jewelry Commission Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) Read more
Seasonal Operations Associate - *Apple* Blo...
Seasonal Operations Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Read more
Hair Stylist - *Apple* Blossom Mall - JCPen...
Hair Stylist - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Blossom 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.