DIRECTORY DragonProcessOffsets, DragOpsCross, DragOpsCrossProcess, DragOpsCrossUtils, HandCoding, HandCodingSupport, HandCodingPseudos; GenStack: CEDAR PROGRAM IMPORTS DragOpsCrossUtils, HandCoding, HandCodingSupport, HandCodingPseudos = BEGIN OPEN DragonProcessOffsets, HandCoding, HandCodingSupport, HandCodingPseudos; CARD: TYPE = LONG CARDINAL; Word: TYPE = DragOpsCross.Word; enableTrapsLit: DragOpsCross.Word = LOOPHOLE[ DragOpsCross.IFUStatusRec[trapsEnabled: TRUE]]; initialFrames: NAT = 256; localFrameArraySize: NAT = 16; StackLog: NAT = 7; emptyFrameLimit: NAT = 1; RegArray: TYPE = ARRAY Reg OF Word; Nacho: TYPE = LONG POINTER TO NachoRep; NachoRep: TYPE = RECORD [ link: Nacho, -- link to previous frame lastPC: Word, -- continuation PC for this frame nRegs: Word, -- number of regs used for this frame at last save others: Nacho, -- if # NIL, then it is a pointer to an aux frame regs: RegArray -- addressable by local regs ]; linkOffset: NAT = 0; constLink: ConstSpec = const0; lastPCOffset: NAT = 1; constLastPC: ConstSpec = const1; nRegsOffset: NAT = 2; constNRegs: ConstSpec = const2; othersOffset: NAT = 3; constOthers: ConstSpec = const3; regOff: CARDINAL = 4; -- offset of DumpBlock.regs LocalAllocationRep: TYPE = RECORD [ lockPtr: GlobalAllocationPtr, -- pointer to global lock for frame allocation ptrs: LocalArray -- start of frame pointers ]; LocalArray: TYPE = ARRAY [0..localFrameArraySize] OF Nacho; GlobalAllocationPtr: TYPE = LONG POINTER TO GlobalAllocationRep; GlobalAllocationRep: TYPE = RECORD [ lock: Word, -- global spin lock for frame allocation gFree: Word, -- pointer to the next free frame in frames emergency: Word, -- pointer to the emergency limit for frames (not yet used) frames: GlobalArray -- space for the global pool of nachos ]; GlobalArray: TYPE = ARRAY [0..initialFrames+1] OF Nacho; StackMargin: NAT _ 17; framesToTransfer: NAT _ 4; stackUnderflowTrap: Label _ NIL; internalSaveEldest: Label _ NIL; globalFreeNacho: Label _ NIL; globalAllocNacho: Label _ NIL; StackUnderflowTrap: PROC = { stackUnderflowTrap: Label = GenLabel[]; setupLabel: Label = GenLabel[]; restoreLabel: Label = GenLabel[]; freeRoutineLabel: Label = GenLabel[]; badLabel: Label = GenLabel[]; notSingleLabel: Label = GenLabel[]; faultLabel: Label = GenLabel[]; flushLabel: Label = GenLabel[]; shortLabel: Label = GenLabel[]; framedLabel: Label = GenLabel[]; area: HandCodingSupport.Area = HandCodingSupport.GetCurrentArea[]; SetLabel[notSingleLabel]; SetEldestPC[]; SetEldestL[]; SetLabel[faultLabel]; Pause[]; SetLabel[stackUnderflowTrap]; MakeLabelGlobal["DragonStack.StackUnderflowTrap", stackUnderflowTrap]; FillTrap[IFUPageFaultTrap, stackUnderflowTrap]; GetYoungestPC[]; drJNEBB[17, UseLabel8B[faultLabel]]; drLIB[19]; SetYoungestPC[]; GetEldestL[]; GetEldestPC[]; drDUP[]; -- so we don't lose it if things are bad drJNEBB[19, UseLabel8B[notSingleLabel]]; drRRX[topDst, hook, constLastPC]; SetEldestPC[]; drDUP[]; SetEldestL[]; drLIB[16]; LRegI[hook, constNRegs]; MoveReg[temp, hook]; MoveRegI[hook, hook, constLink]; drRJLEBJ[left: topSrc, right: belowSrc, dist: UseLabel8B[shortLabel]]; { loopLabel: Label = GenLabelHere[]; FOR i: NAT IN [0..15] DO drRAI[reg1: [reg[i]], reg2: temp, disp: regOff+i]; ENDLOOP; LReg[temp]; MoveRegI[temp, temp, constOthers]; FreeNacho[]; drAL[16]; drSUBB[16]; drRJGB[left: topSrc, right: belowSrc, dist: UseLabel8B[loopLabel]]; }; SetLabel[shortLabel]; { jumpLabel: Label = GenLabel[]; drRVADD[c: belowDst, a: topSrc, b: topSrc]; drRVADD[c: belowDst, a: belowSrc, b: belowSrc]; drRVSUB[c: belowDst, a: popSrc, b: belowSrc]; IndexedJump[dest: jumpLabel]; FOR i: NAT DECREASING IN [0..15] DO drRAI[reg1: [reg[i]], reg2: temp, disp: regOff+i]; ENDLOOP; SetLabel[jumpLabel]; LReg[temp]; FreeNacho[]; }; { noFrameLabel: Label = GenLabel[]; THROUGH [0..emptyFrameLimit) DO HandCoding.drRJEB[left: const0, right: hook, dist: UseLabel8B[noFrameLabel]]; LRegI[hook, constNRegs]; HandCoding.drRJNEBJ[left: const0, right: popSrc, dist: UseLabel8B[noFrameLabel]]; drDUP[]; LRegI[hook, constLastPC]; SetEldestPC[]; SetEldestL[]; LReg[hook]; MoveRegI[hook, hook, constLink]; FreeNacho[]; ENDLOOP; SetLabel[noFrameLabel]; MakeLabelGlobal["DragonStack.StackUnderflowExit", noFrameLabel]; drLIB[17]; SetEldestPC[]; { noHookLabel: Label = GenLabel[]; drDUP[]; drRJEB[left: const0, right: hook, dist: UseLabel8B[noHookLabel]]; LRegI[hook, constNRegs]; drSUB[]; SetLabel[noHookLabel]; ExtractField[first: 32-StackLog, bits: StackLog]; SetEldestL[]; }; drSUBB[StackMargin]; ExtractField[first: 32-StackLog, bits: StackLog]; SetSPLimit[]; drALS[0]; MakeLabelGlobal["DragonStack.StackUnderflowReturn", GenLabelHere[]]; drRETK[377B]; }; }; StackOverflowTrap: PROC = { exitLabel: Label _ GenLabel[]; { ifuEntryLabel: Label = GenLabel[]; ProcedureEntry[ifuEntryLabel, 1]; MakeLabelGlobal["DragonStack.IFUStackOverflowTrap", ifuEntryLabel]; FillTrap[IFUStackOverflowTrap, ifuEntryLabel]; GetEldestPC[]; drDIS[]; drLFC[UseLabel16[internalSaveEldest]]; drJB[UseLabel8A[exitLabel]]; }; { euEntryLabel: Label = GenLabel[]; ProcedureEntry[euEntryLabel, 1]; MakeLabelGlobal["DragonStack.EUStackOverflowTrap", euEntryLabel]; FillTrap[EUStackOverflowTrap, euEntryLabel]; GetEldestPC[]; drDIS[]; { loopLabel: Label = GenLabelHere[]; drLFC[UseLabel16[internalSaveEldest]]; LRegI[hook, constNRegs]; drRJEB[left: popSrc, right: const0, dist: UseLabel8B[loopLabel]]; }; }; { SetLabel[exitLabel]; MakeLabelGlobal["DragonStack.StackOverflowExit", exitLabel]; GetEldestL[]; drLIB[17]; SetEldestPC[]; LRegI[hook, constNRegs]; drRVSUB[topDst, belowSrc, topSrc]; ExtractField[first: 32-StackLog, bits: StackLog]; SetEldestL[]; drSUBB[StackMargin]; ExtractField[first: 32-StackLog, bits: StackLog]; SetSPLimit[]; MakeLabelGlobal["DragonStack.StackOverflowReturn", GenLabelHere[]]; drRETK[377B]; }; }; InternalSaveEldest: PROC = { setupLabel: Label = GenLabel[]; { localHook: RegSpec = reg0; localNRegs: RegSpec = reg1; ProcedureEntry[setupLabel, 1]; LReg[hook]; drPSB[linkOffset]; PReg[hook]; PReg[temp]; GetEldestL[]; drDUP[]; SetYoungestL[]; GetEldestPC[]; drSRIn[localHook, lastPCOffset]; GetEldestL[]; drRVSUB[c: localNRegs, a: popSrc, b: localNRegs]; ExtractField[first: 32-StackLog, bits: StackLog]; drWRI[localNRegs, localHook, nRegsOffset]; drLIB[16]; SReg[localHook]; drRETN[]; }; { shortLabel: Label = GenLabel[]; SetLabel[internalSaveEldest]; MakeLabelGlobal["DragonStack.InternalSaveEldest", internalSaveEldest]; AllocNacho[]; drLFC[UseLabel16[setupLabel]]; drRJLEBJ[left: topSrc, right: belowSrc, dist: UseLabel8B[shortLabel]]; {loopLabel: Label = GenLabelHere[]; FOR i: NAT IN [0..15] DO drWAI[reg1: [reg[i]], reg2: temp, disp: regOff+i]; ENDLOOP; LReg[temp]; AllocNacho[]; PReg[temp]; drWSB[othersOffset]; drAL[16]; drSUBB[16]; drRJGB[left: topSrc, right: belowSrc, dist: UseLabel8B[loopLabel]]; }; SetLabel[shortLabel]; { jumpLabel: Label = GenLabel[]; drRVADD[c: belowDst, a: topSrc, b: topSrc]; drRVADD[c: belowDst, a: belowSrc, b: belowSrc]; drRVSUB[c: belowDst, a: popSrc, b: belowSrc]; IndexedJump[jumpLabel]; FOR i: NAT DECREASING IN [0..15] DO drWAI[reg1: [reg[i]], reg2: temp, disp: regOff+i]; ENDLOOP; SetLabel[jumpLabel]; }; drRETN[]; }; }; AllocNacho: PROC = { exitLabel: Label = GenLabel[]; enterLabel: Label = GenLabelHere[]; LRegI[free, const0]; drRJNEBJ[left: topSrc, right: const0, dist: UseLabel8B[exitLabel]]; drLFC[UseLabel16[globalAllocNacho]]; drJB[UseLabel8A[enterLabel]]; SetLabel[exitLabel]; AddReg[free, const1]; drLC0[]; drPSB[othersOffset]; }; GlobalAllocNacho: PROC = { exitLabel: Label = GenLabel[]; globalAllocNacho _ GenLabelHere[]; MakeLabelGlobal["DragonStack.GlobalAllocNacho", globalAllocNacho]; drRRX[c: topDst, a: base, b: const0]; LReg[process]; drLC0[]; {retryLabel: Label = GenLabelHere[]; drCST[0]; drRJNEB[left: popSrc, right: belowSrc, dist: UseLabel8B[retryLabel]]; drAS[256-2]; }; SubReg[free, const4]; drRSB[1]; FOR i: NAT IN [0..framesToTransfer) DO drRSB[i]; LReg[free]; drWB[i]; ENDLOOP; drADDB[framesToTransfer]; drPSB[1]; drLC0[]; drWSB[0]; drRETN[]; }; FreeNacho: PROC [] = { exitLabel: Label = GenLabel[]; enterLabel: Label = GenLabelHere[]; drRVSUB[c: pushDst, a: free, b: const1]; drRJNEBJ[left: topSrc, right: base, dist: UseLabel8B[exitLabel]]; drLFC[UseLabel16[globalFreeNacho]]; SetLabel[exitLabel]; PReg[free]; drWB[0]; }; GlobalFreeNacho: PROC = { globalFreeNacho _ GenLabelHere[]; MakeLabelGlobal["DragonStack.GlobalFreeNacho", globalFreeNacho]; drRRX[c: topDst, a: base, b: const0]; LReg[process]; drLC0[]; {retryLabel: Label = GenLabelHere[]; drCST[0]; drRJNEB[left: popSrc, right: belowSrc, dist: UseLabel8B[retryLabel]]; drAS[256-2]; }; drRSB[1]; drSUBB[4]; FOR i: NAT IN [0..4) DO LReg[free]; drRB[i]; drPSB[i]; ENDLOOP; drPSB[1]; drLC0[]; drWSB[0]; drRVADD[c: pushDst, a: free, b: const3]; drRETN[]; }; GenFramesInit: PROC = { allocator: Label = HandCodingPseudos.GetGlobalLabel["Basics.AllocVector"]; rZero: RegSpec = reg0; rLB: RegSpec = reg1; -- base of local frame table rSB: RegSpec = reg2; -- base of shared frame table tPtr: RegSpec = reg3; -- pointer to next slot in global table drLC0[]; -- init rZero drLIB[SIZE[LocalAllocationRep]/2]; drLFC[UseLabel16[allocator]]; drROR[base, topSrc, const0]; drLIDB[4+4+initialFrames]; drLFC[UseLabel16[allocator]]; drWRI[rSB, rLB, 0]; drWRI[rZero, rSB, 0]; drWRI[rZero, rSB, 2]; drRVADD[pushDst, rSB, const3]; drWRI[tPtr, rSB, 1]; {loopLabel: Label = GenLabelHere[]; drLIB[20]; drLFC[UseLabel16[allocator]]; drSRIn[tPtr, 0]; drRVADD[tPtr, tPtr, const1]; drLRn[tPtr]; drSUBDB[initialFrames]; drRJNEBJ[left: popSrc, right: rSB, dist: UseLabel8B[loopLabel]]; }; drLIB[17]; drRADD[free, base, popSrc]; drWRI[rZero, rLB, 17]; drAS[256-4]; }; All: PROC = { continueLabel: Label = GenLabel[]; internalSaveEldest _ GenLabel[]; GenFramesInit[]; drLFC[UseLabel16[continueLabel]]; GlobalAllocNacho[]; GlobalFreeNacho[]; InternalSaveEldest[]; StackUnderflowTrap[]; StackOverflowTrap[]; SetLabel[continueLabel]; drLIB[17]; SetYoungestPC[]; EnableTraps[]; MakeLabelGlobal["DragonStack.ExitToUser", GenLabelHere[]]; }; FillTrap: PROC [tx: DragOpsCross.TrapIndex, dest: Label] = { area: HandCodingSupport.Area = HandCodingSupport.GetCurrentArea[]; oldPC: INT = HandCodingSupport.GetOutputPC[area]; SetOutputPC[DragOpsCrossUtils.TrapIndexToBytePC[tx]]; drJDB[UseLabel16[dest]]; HandCodingSupport.SetOutputPC[oldPC]; }; END. <ζGenStack.mesa Copyright c 1985, 1986 by Xerox Corporation. All rights reserved. Russ Atkinson (RRA) February 28, 1986 2:32:00 pm PST GenStack.All[] generates code for stack saving and restoring. Size parameters (the only important difference between this file and GenBigStack.mesa) Initial frames to allocate. # of frames in localArray Note: StackSize = 2^StackLog The stack underflow routine is prepared to restore the youngest frame (in hook) and this many empty frames immediately elder than the youngest frame. This avoids the situation where we underflow into an "empty" frame, then execute an ALS instruction which effectively moves registers from the youngest frame to the next youngest. If we allowed that to happen we would lose those registers from the stack abstraction, which would be wrong! type of holder for frames per processor, limit is quite arbitrary (need not be fixed) NIL is stored at the very end to make test for empty easy type of holder for frames, limit is quite arbitrary (need not be fixed) NIL is stored at the very end to make test for empty easy Number of words in EU stack to reserve to handle stack overflow. Will this really be enough? This has hardware implications as well (see Don Curry) Number of frames to transfer between local and global frame pools. Global labels Entry point for handling stack underflow (aka DragonStack.StackUnderflowTrap). Also used as the PC for the bogus frame. Entry point for the internal routine (aka DragonStack.InternalSaveEldest) that saves the eldest frame. Entry point for the internal routine that frees up a nacho to the central pool. Entry point for the internal routine that allocates up a nacho to the central pool. This code is called when we return to the bogus frame, which has an invalid PC. At entry, maskable traps are disabled, and the IFU stack has exactly 1 frame (if the world is valid). The top of stack has exactly one word, which is the saved status. The idea is to just bring in one frame from the hook, and then "return" to it, enabling traps as we go. Entry point for handling stack underflow (aka DragonStack.StackUnderflowTrap). At this point we have a case where the eldest PC # the youngest PC, and the stack has [S] = eldest PC, [S-1] = eldest L, [S-2] = status. The IFU stack is not empty. At this point we a genuine page fault (or just maybe the bogus frame has been clobbered). [S] = status. The IFU stack is as at entry. We enter this procedure with one argument, the saved status word. However, we don't want to set L, since that would make restoring the regs harder. At this point we should determine if the IFU stack only has the bogus frame. At this point we had one frame on the stack, and it was the bogus frame. So we put on the new value for the eldest frame PC. Get the new eldest PC into the IFU stack Set the L value for that frame. Push 16, then put the # of registers in [S] ([S] = #regs, [S-1] = 16) Put the first frame to restore in temp Make the hook point to the next frame (hook _ (hook+0)^) If #regs <= 16 (the usual case), skip the code that dumps extra blocks. At this point, nregs > 16, so dump the first 16. Now do 16 reads into the stack registers from the dump block push the nacho to free; point temp at the next nacho in the chain ([S] = nextNacho; [S-1] = #regs; [S-2] = 16) free the nacho pointed to by [S]; S_S-1 adjust L and #regs ([S] = #regs left; [S-1] = 16) go do another frame (if necessary), do not change S This is point where we restore frames without extensions, and also restore the remnant of frames with extensions. [S] = #regs; [S-1] = 16. The best way to quickly restore a variable # of regs is to jump into a table of read instructions. We don't dare restore too much or we will clobber the potential return values. ([S] = #regs; [S-1] = 2*#regs) ([S] = #regs; [S-1] = 4*#regs) ([S] = -3*#regs) jump into the table free the nacho pointed to by temp (no change to S) At this point all of the registers have been restored, all of the dump blocks have been freed. [S] holds the L for the restored frame, and [S-1] holds the status word. The eldest frame is the restored frame, and there is no bogus frame. The following code restores some number of empty frames. This is an attempt to avoid the situation where we get a fault before performing the ALS instruction. Since the ALS instruction effectively moves ownership of registers from the youngest frame to the next youngest, we must be sure that there IS a next youngest frame to move the registers to! Jump for an empty hook (should be rare) Jump for a hook that is non-empty Now the EU stack has the L and PC for the empty frame. This puts the empty frame on the IFU stack. push the hook, and put the next eldest frame link in hook free the nacho pointed to by [S]; S_S-1 [S] has L for eldest frame on IFU stack, [S-1] has the saved status Install the new bogus frame & set its PC It is possible that there is no hook left, so don't blow it by dereferencing through it. [S] = [S-1] = L for eldest frame in IFU stack Calculate & set the L for the bogus frame. [S] still holds the L for the last restored frame, [S-1] holds the status. Calculate & set the new stack limit. [S] now holds only the status. We must finally set L to be the same as S so we can execute the RETK properly. [S] still holds the status. Return from kernel, cutting back the stack appropriately. Note: we assume that there is sufficient reserve space on the EU stack and the IFU stack to complete the saving of one frame. Traps are automatically disabled on entry to this routine, and must be reenabled on the way out. DragonStack.IFUStackOverflowTrap: This part is for IFU stack overflow. Note that we are NOT assured of a non-empty frame on the IFU stack. We get one argument, which is the status word. discard the bogus frame Call to save eldest frame DragonStack.EUStackOverflowTrap: If we save a frame, but don't get any more space in the EU stack, then we have to keep saving frames until a frame is saved that has at least one EU register saved with it. We know that there is a non-empty frame on the register stack, otherwise why would we get an EU stack overflow? We get one argument, which is the status word. discard the bogus frame Call to save one frame If nregs = 0, then loop to the start. We must get at least one word saved to terminate. Of course, at least one frame must have more than 0 words in order to get the EU stack overflow trap in the first place, so termination is assured. This is the common exit stuff for the stack overflow handlers. The idea is to keep the stack limit register set with enough reserve space to be able to prevent wraparound when we execute code where traps are disabled. Also, the saved L for the bogus frame must be consistent with the number of registers in the youngest saved frame (referenced by hook). Get the L for the restored frame on the stack. We use it copiously later. Install the new bogus frame & set its PC Calculate & set the L for the bogus frame. [S] still holds that L. Calculate & set the new stack limit. S is now back to its original depth. At this point we go back to the code that overflowed. The old status word is used to restore the user/kernel mode. This routine saves the eldest frame. This routine is intended for use ONLY by the various overflow and reschedule trap routines. We assume that the bogus frame has been removed by the caller. This is an internal routine that we use to setup stuff (especially L) prior to saving the frame. It needs to be a procedure because we have to set L (sigh). before entry: [S] = newBlock; [S-1] = PC for dummy frame; hook = frame chain after exit: [S] = #regs; [S-1] = 16; L = L of frame to save Make our local L good for a few locals, we get one sent to us on the stack store the hook into the new dump block ([S] = localHook = newBlock; (localHook+linkOffset)^ = hook) store the new dump block addr into hook and temp ([S] = localHook = hook = temp = newBlock) Get the L for the frame we wish to save, put it into localNRegs and youngest L ([S] = localNRegs = L of frame to save; [S-1] = localHook) Store the continuation PC and remove the eldest PC from the ifuStack. ((localHook+lastPCOffset)^ = PC of frame to save) Calculate the number of regs in this frame ([S] = localNRegs = eldestL - localNRegs'; [S-1] = localHook) determine the # of regs to store, using modulo arithmetic ([S] = localNRegs = #regs = (eldestL - localNRegs') MOD StackSize) Save #regs into the save block (localHook+nRegsOffset)^ = localNRegs ([S] = #regs; [S-1] = 16) return without S adjustment DragonStack.InternalSaveEldest: This is the entry point for internally saving the eldest stack frame in the IFU stack. The bogus frame has been removed. Allocate the next save block to use ([S] = newBlock) Init the new save block. Its address is left in hook. L gets set to the L for the frame we want to save. In addition: ([S] = #regs; [S-1] = 16) If #regs <= 16 (the usual case), skip the code that dumps extra blocks. At this point, there nregs > 16, so dump the first 16. The save block to use has already been allocated, and its address is in temp. Push the address of the completed save block ([S] = temp = oldBlock; [S-1] = #regs; [S-2] = 16) Allocate the next save block to use (it gets left on the stack) ([S] = newBlock; [S-1] = temp = oldBlock; [S-2] = #regs; [S-3] = 16) set temp to the new dump block addr also store the new block addr into the old block (temp = (temp'+othersOffset)^ = newBlock; [S] = #regs; [S-1] = 16) adjust L and #regs ([S] = #regs; [S-1] = 16) go do another frame (if necessary) (#regs IN [0..16]; [S] = #regs; [S-1] = 16) The best way to quickly restore a variable # of regs is to jump into a table of read instructions. This takes roughly 6 cycles to do the jump, and we stand to save at least one cycle for every store we save (not counting avoiding extra dirty cache entries). ([S] = #regs; [S-1] = 2*#regs) ([S] = #regs; [S-1] = 4*#regs) ([S] = -3*#regs) jump into the table Generate 16 stores of locals to the save block This return does not enable traps, and does not disturb S, but does restore L, which was previously clobbered. S must have the same value that it did at entry! Allocate a nacho using the local array of nachos, defaulting to the global array of nachos if not immediately successful. The address of the allocated nacho is left on the stack. There is no provision for failure from the global array at this time. Push the next nacho address. If none in our local cache, a 0 will be pushed. Jump if we got the nacho; leave 0 on stack if not. Predict success. Call to do this the expensive way Go to retry the allocation from the start (stack is back to ground level). This is the successful exit point. The allocated nacho is on the stack. Adjust the free pointer, since we got a nacho always clears the others field on allocation Replenish the local nacho array from the global nacho array. There is no provision for failure from the global array at this time. At entry, [S] = 0, at exit S_S-1, but the local array has nachos. AllocNacho is the only caller of this routine! Replace top of stack (was 0) with the addr of the lock. ([S] = @lock) Push the desired new value for the lock field ([S] = process; [S-1] = @lock) Push the assumed old value of the lock field (i.e. free) ([S] = 0; [S-1] = process; [S-2] = @lock) Try for the global lock for the nacho allocator. We store our process ID into the lock if the lock was free, and return the sampled value of the lock at the start of the instruction in any case. ([S] = sample; [S-1] = 0; [S-2] = process; [S-3] = @lock) Jump back to retry if we did not get it (predict success), and pop the sampled value. If this loop causes us to hold the bus too often, we can always insert a spin loop that does not use CST. ([S] = 0; [S-1] = process; [S-2] = @lock) On success, flush the old & new values, since we don't need them. ([S] = @lock) Adjust the free pointer to accomodate the next transfers. Get the global free pointer (gFree) on the stack (@base.gFree = @base.lock + 1) ([S] = gFree; [S-1] = @lock) (free+i)^ _ (gFree+i)^ adjust gFree for the number of nachos allocated ([S] = new gFree; [S-1] = @lock) Write gFree back, leaving the addr of the lock on the stack. ([S] = @lock) Clear out the lock, which lets other processors get their chance. (stack is now at original level) Free a nacho (in [S]) using the local array of nachos, defaulting to the global array of nachos if not immediately successful. There is no provision for failure from the global array at this time. [S] = free-1; [S-1] = nacho to free Determine if free-1 will collide with base, jump if not. Free-1 is left on the stack for use in storing away the freed frame. Predict success. In the hard case we call a routine to munch on the global table. At this point the address of the slot to hold the nacho is on the stack. First we store that address to free, then we load the nacho to be freed and store it into the slot. (free _ [S])^ _ [S-1]; S_S-2 Free up a nacho (in [S-1]) to the central pool. We have already tested for the fast case, and we call this when [S] = free-1; [S-1] = nacho to free. At exit, [S] = new free, [S-1] = nacho to free. Determine if free-1 will collide with base, jump if not. Free-1 is left on the stack for use in storing away the freed frame. Predict success. Put the addr of the lock on the stack. We get to have a pop for free here. ([S] = @lock) Push the desired new value for the lock field ([S] = process; [S-1] = @lock) Push the assumed old value of the lock field (i.e. free) ([S] = 0; [S-1] = process; [S-2] = @lock) Try for the global lock for the nacho allocator. We store our process ID into the lock if the lock was free, and return the sampled value of the lock at the start of the instruction in any case. ([S] = sample; [S-1] = 0; [S-2] = process; [S-3] = @lock) Jump back to retry if we did not get it (predict success), and pop the sampled value. If this loop causes us to hold the bus too often, we can always insert a spin loop that does not use CST. ([S] = 0; [S-1] = process; [S-2] = @lock) On success, flush the old & new values, since we don't need them. The lock address is left on the stack. ([S] = @lock) get the global free pointer (gFree) on the stack (leaving the lock addr under it) ([S] = gFree; [S-1] = @lock) gFree _ gFree - 4; leave gFree on stack ([S] = new gFree; [S-1] = @lock) (gFree+i)^ _ (free+i)^ write gFree back, leaving the lock addr on the stack ([S] = @lock) clear out the lock, which lets other processors get theirs (stack is now at original level) ([S] = free + (4-1)) This is the successful exit point. There is room between free and base. allocate the per processor frame base (LocalAllocationRep) also put that frame into base and leave in rLB allocate space for the shared frame base (GlobalAllocationRep) also store that address into rLB.lockPtr and leave it in rSB clear out the shared frame base init rSB.gFree and tPtr Allocate the new frames from the basic system allocator. Each frame gets stuck into the shared frame base (GlobalAllocationRep) in a new slot. Allocate and store the new frame stop when tPtr gets far enough from the base now make free point at the next local slot to fill also, clear out that slot Finally, drop the junk from the stack Entry point for the internal routine (aka DragonStack.InternalSaveEldest) that saves the eldest frame. Order of generation is important! Setup the bogus frame & enable traps (to detect stack overflow). Κe–81.25 in leftMargin 1.25 in rightMargin 6.0 in lineLength˜codešœ ™ Kšœ Οmœ7™BK™4—˜šœ=™=K™šΟk ˜ Kšœ˜Kšœ ˜ Kšœ˜Kšœ˜Kšœ ˜ Kšœ˜Kšœ˜———headšœ žœž˜KšžœD˜KKšœžœžœH˜TK˜K–20 sp tabStopsšžœžœžœžœ˜K–20 sp tabStopsšœžœ˜K–20 sp tabStopsšœ#ž œ*žœ˜]K–20 sp tabStops˜–20 sp tabStops™VJ–20 sp tabStops˜–20 sp tabStopsšœžœ˜J–20 sp tabStopsšœ™—–20 sp tabStopsšœžœ˜J–20 sp tabStopsšœ™—J–20 sp tabStops™—–20 sp tabStopsšœ žœ˜K–20 sp tabStopsšœ™—K–20 sp tabStops˜–20 sp tabStopsšœžœ˜K–20 sp tabStopsšœΈ™Έ—K–20 sp tabStops˜K–20 sp tabStopsšœ žœžœžœ˜#K–20 sp tabStopsš œžœžœžœžœ ˜'–36 sp tabStopsšœ žœžœ˜K–36 sp tabStopsšœ Οc˜&K–36 sp tabStopsšœŸ!˜/K–36 sp tabStopsšœ Ÿ2˜?K–36 sp tabStopsšœŸ1˜@K–36 sp tabStopsšœŸ˜+K–36 sp tabStopsšœ˜–36 sp tabStopsšœ žœ˜K–36 sp tabStopsšœ˜—–36 sp tabStopsšœžœ˜K–36 sp tabStopsšœ ˜ —–36 sp tabStopsšœ žœ˜K–36 sp tabStopsšœ˜—–36 sp tabStopsšœžœ˜K–36 sp tabStopsšœ ˜ —K–36 sp tabStopsšœžœŸ˜1—K˜–36 sp tabStopsšœžœžœ˜#K–36 sp tabStopsšœŸ.˜LK–36 sp tabStopsšœŸ˜+K–36 sp tabStopsšœ˜–24 sp tabStopsšœ žœžœžœ˜;K–24 sp tabStopsšœU™UK–24 sp tabStops™9——K–24 sp tabStops˜K–24 sp tabStopsš œžœžœžœžœ˜@–24 sp tabStopsšœžœžœ˜$K–24 sp tabStopsšœ Ÿ(˜4K–24 sp tabStopsšœ Ÿ+˜8K–24 sp tabStopsšœŸ;˜LK–24 sp tabStopsšœŸ&˜:K–24 sp tabStopsšœ˜–24 sp tabStopsšœ žœžœžœ˜8K–24 sp tabStopsšœG™GK–24 sp tabStops™9——K˜šœ žœ˜Kšœ•™•—šœžœ˜KšœB™B—K–24 sp tabStops™–24 sp tabStopsšœ ™ K–24 sp tabStops˜–24 sp tabStopsšœžœ˜ K–24 sp tabStopsšœx™x—–24 sp tabStopsšœžœ˜ K–24 sp tabStopsšœf™f—–24 sp tabStopsšœžœ˜K–24 sp tabStopsšœO™O—–24 sp tabStopsšœžœ˜K–24 sp tabStopsšœS™S——K–24 sp tabStops™šΟnœžœ˜K™αK˜–24 sp tabStopsšœ'˜'K–24 sp tabStopsšœN™N—Kšœ˜Kšœ!˜!Kšœ%˜%Kšœ˜Kšœ#˜#Kšœ˜Kšœ˜Kšœ˜Kšœ ˜ KšœB˜BK˜šœ˜Kšœ₯™₯—K˜K˜ šœ˜Kšœ‡™‡—Kšœ˜K™šœ˜Kšœ”™”—KšœF˜FKšœ/˜/K˜KšœL™LK˜Kšœ$˜$K˜ K˜K˜ K˜Kšœ Ÿ(˜2Kšœ(˜(K˜Kšœ}™}K™šœ1˜1Kšœ(™(—˜Kšœ™—šœ$˜$šœ)žœ™+Kšœžœ žœ ™——šœ˜Kšœ&™&—šœ ˜ Kšœ8™8K™—šœF˜FKšœG™GK˜—šœ˜Kšœ0™0K˜Kšœ"˜"K™KšŸ<™<šžœžœžœ ž˜Kšœ2˜2Kšžœ˜K˜—šœ.˜.™AKšœžœžœžœ ™,——˜ Kšœ'™'—šœ˜Kšœžœžœžœ ™2—šœC˜CK™3—K˜K˜—šœ˜Kšœtžœ žœ ™‹K˜—šœ˜Kšœ²™²K˜Kšœ˜K˜šœ+˜+Kšœžœ žœ™—šœ/˜/Kšœžœ žœ™—šœ-˜-Kšœžœ ™—šœ˜Kšœ™—K˜š žœžœž œžœ ž˜#Kšœ2˜2Kšžœ˜—Kšœ˜šœ˜Kšœ0žœ™2—K˜K˜—˜Kšœξ™ξK˜K˜!K˜Kšœί™ίšžœž˜˜MKšœ'™'—Kšœ˜˜QK™!—šœ"˜"Kšœ6™6—˜Kšœ+™+—˜,Kšœ9™9—šœ ˜ Kšœ'™'—Kšžœ˜K˜—K˜šœ@˜@Kšœžœ"™CK˜—šœ˜Kšœ(™(—˜KšœX™XKšœ ˜ šœ˜Kšœ-™-—KšœA˜AKšœ!˜!Kšœ˜šœ?˜?Kšœv™v—K˜K™—šœU˜UKšœD™DK˜—˜ Kšœk™k—KšœD˜D˜ Kšœ9™9—K˜—K˜K˜K˜—š œžœ˜Kšœί™ίK˜K˜˜KšΟb œk™‹Kšœ"˜"šœ!˜!Kšœ.™.—K˜KšœC˜CKšœ.˜.K˜˜Kšœ™K™—šœ&˜&Kšœ™K™—Kšœ˜K˜—šœ˜Kš‘œŸ™ΎKšœ!˜!šœ ˜ Kšœ.™.—K˜KšœA˜AKšœ,˜,K˜˜Kšœ™—K˜šœ˜Kšœ"˜"K˜šœ&˜&Kšœ™—K˜Kšœ˜šœA˜AKšœν™ν—K˜—K˜—˜Kšœγ™γK˜Kšœ<˜—šœ ™ K™/—K˜—Kšœ˜Kšœ˜K˜šœ˜KšœJ™J—K˜šœ˜šœ&™&Kšœžœ9™<——šœ˜šœ0™0Kšœžœ'™*——šœ(˜(šœN™NKšœžœžœžœ™:——šœ0˜0šœE™EKšœžœ™1——šœ@˜@šœ*™*Kšœžœ)žœ™=——šœ1˜1šœ9™9Kšœžœ1žœ ™BK™——šœ*˜*šœ™Kšœ%™%——K™šœ˜Kšœžœ žœ ™—˜ Kšœ™—K˜K˜—šœ˜Kš‘œ{™™K˜Kšœ˜K˜Kšœ˜KšœF˜FK˜˜ šœ#™#K™——K˜šœ˜šœx™xKšœ™——K˜šœF˜FKšœG™GK˜—šœ#˜#K™Kšœ…™…K˜šžœžœžœ ž˜Kšœ2˜2Kšžœ˜—K˜šœ ˜ šœ,™,Kšœ2™2——˜ šœ?™?KšœD™D——šœ!˜!K™#™0KšœB™B——šœ˜™K™——šœC˜CK™"—K˜K™—šœ˜Kšœžœ"™+K˜—šœ˜Kšœ‚™‚K˜Kšœ˜K˜šœ+˜+Kšœ™—šœ/˜/Kšœ™—šœ-˜-Kšœ™—šœ˜Kšœ™—K˜š žœžœž œžœ ž˜#Kšœ.™.Kšœ2˜2Kšžœ˜—K˜Kšœ˜K˜—K˜šœ ˜ Kšœ ™ —K˜—Kšœ˜K˜—š  œžœ˜Kšœ΅‘E™ϊK˜Kšœ˜Kšœ#˜#K˜šœ˜KšœM™M—K˜šœC˜CKšœD™DK˜˜$Kšœ!™!—šœ˜KšœJ™J——K˜˜KšœH™H—K˜šœ˜Kšœ-™-—šœ˜Kšœ,™,—K˜K˜—š œžœ˜Kšœ>‘E™ƒK™qK˜Kšœ˜Kšœ"˜"KšœB˜BK˜˜%šœ7™7K™ ——šœ˜šœ-™-K™——˜šœ8™8K™)——K˜˜$šœ ˜ šœΓ™ΓK™9——šœE˜Ešœΐ™ΐK™)——˜ šœA™AK™ ——K˜—K˜šœ˜Kšœ9™9—˜ šœ0™0Kšœ™K™——šžœžœžœž˜&šœ ˜ K™—Kšžœ˜—šœ˜šœ/™/K™ ——˜ šœ<™K˜Kšœ Ÿ ˜Kšœžœ˜"šœ;˜;Kšœ:™:Kšœ.™.—K˜šœN˜NKšœ>™>Kšœ<™<—K˜šœ,˜,Kšœ™—K˜šœ4˜4Kšœ™—K˜Kšœ‘™‘˜#šœ;˜;Kšœ ™ —Kšœ˜Kšœ%˜%šœ@˜@Kšœ,™,—K˜K˜—šœ?˜?Kšœ2™2K™—K˜˜ Kšœ%™%—K˜K˜—š œžœ˜ K˜K˜"K˜–24 sp tabStopsšœ ˜ K–24 sp tabStopsšœf™f—Kšœ˜K˜K˜!K˜Kšœ!™!K˜K˜Kšœ˜Kšœ˜Kšœ˜K˜K˜K˜Kšœ@™@K˜Kšœ ˜ K˜šœ˜K˜—Kšœ:˜:K˜K˜K˜—š œžœ.˜