*----------------------------------------------------------- Title[DMesaMiscOps.mc...January 27, 1984 1:13 PM...Taft]; * MISC entry point; miscellaneous MISC opcodes -- groups 000, 100, and 240. *----------------------------------------------------------- % CONTENTS, by order of alpha byte value Defined on both Dorado and Dolphin: alpha=0 Associate alpha=1 SetFlags alpha=2 (read ram unimplemented) alpha=3 LoadRam alpha=4 (IOReset unimplemented) alpha=5 Input alpha=6 Output alpha=7 Checksum alpha=10b Set maintenance panel (PrincOps only) alpha=11b ReadClock alpha=12b GenIOin alpha=13b GenIOout (diablo interface) alpha=14b (Xfer Long de-implemented) alpha=15b (TextBlt unimplemented) (was Write MDS for all tasks -- de-implemented) alpha=16b GetFlags alpha=17b Set default disk partition (Alto only) alpha=100b LocalBlkZ alpha=102b LongBlkZ alpha=104b Version (implemented in DMesaVersion.mc) Special operations defined on Dorado only: alpha=240b Zero and Enable Event counters alpha=241b Read Event counters alpha=242b Stop Event counters alpha=243b Set PC Histogram Address alpha=244b Unused alpha=245b Unused alpha=246b Read/write muffler/manifold system alpha=247b Reset Ethernet hardware and tasks (PrincOps only) alpha=250B Unused (used to be Boot; PrincOps only) alpha=251B Get size of real and virtual memory alpha=252B Halt Dorado (for timed power-off) alpha=253B Set display field rate alpha=254b Reset disk hardware and task (PrincOps only) alpha=255b Set interval timer (PrincOps only) alpha=256b Stable Storage block input alpha=257b Stable Storage block output % TopLevel; *----------------------------------------------------------- IFUR[MISC, 2, MDS]; * Do miscellaneous operation alpha *----------------------------------------------------------- T_ (2(ID)) LSH 1, Branch[MISCM1]; :IfMEP; T_ (2(ID)) LSH 1, Stack_ MD, Branch[MISCM1]; T_ (2(ID)) LSH 1, StkP+1; :If[AltoMode]; ********** Alto version ********** T_ T+1; * Remember entry point 2 :EndIf; ********************************** :EndIf; MISCM1: RTemp1_ LDF[T, 4, 6]; BigBDispatch_ RTemp1; :If[AltoMode]; ********** Alto version ********** OTPReg_ BigBDispatch_ T, Branch[MiscDispatch]; :Else; ******** PrincOps version ******** BigBDispatch_ T, Branch[MiscDispatch]; :EndIf; ********************************** * Upon dispatch, T contains TOS (if there is one) and StkP has been advanced * in preparation for pushing a result. Routines that do not push a result * must decrement StkP. * Alto mode: OTPReg contains 4*alpha if entry point 0 or 1 was * used, 4*alpha+1 if entry point 2 (used by floating point trap handler). * Spread the entry points 4 apart and put them at odd locations. * This is so that the first instruction can do a Call if desired, and so that * call locations and some conditional branch targets are preserved. * alpha=0, 1, ... 77 => dispatch 1, 5, ... 375 into MiscTable0, * alpha=100, 101, ... 177 => dispatch 1, 5, ... 375 into MiscTable1, etc. *----------------------------------------------------------- * Some definitions for Mesa's record that holds a page number and map flags *----------------------------------------------------------- * MapEntry: TYPE = MACHINE DEPENDENT RECORD [ * unused, wProtect, dirty, ref: BOOLEAN, realPage: [0..7777B]]; MC[MesaF&P.wProtect, 40000]; MC[MesaF&P.dirty, 20000]; MC[MesaF&P.ref, 10000]; MC[MesaF&P.wProtect&dirty, MesaF&P.wProtect, MesaF&P.dirty]; MC[MesaF&P.flagsMask, 70000]; MC[MesaF&P.pageMask, 7777]; * Mesa defines vacant as wProtect and dirty and ref'. * Unfortunately, the Dorado defines vacant as wProtect and dirty, * without regard to ref. * To get around this problem, we take over one of the two high-order * bits of the real page number, which do not participate in storage * addressing unless 256K storage chips are installed (unlikely * during the lifetime of the Dorado). * When Mesa asks us to set the combination wProtect and dirty and ref * (which is NOT vacant by Mesa's definition), we instead set * wProtect and dirty' and ref, and we set the extra bit. * When Mesa asks to read the flags, we or together the hardware dirty * bit and the extra bit. *----------------------------------------------------------- Associate: MiscTable[0], * m: MapEntry _ Pop[]; vp _ Pop[]; Map[vp] _ m; *----------------------------------------------------------- T_ MD, StkP-2; T_ Stack&+1, Call[SetBRForPage]; T_ Stack&-2, Call[WriteMapPage]; * Restart IFU, since FlushPage (called from WriteMapPage) reset it. AssocExit: T_ (ID)-(PCX')-1; * T_ PCX+IL IFUReset, Branch[SetPCAndJump0]; *----------------------------------------------------------- SetFlags: MiscTable[1], * newM: MapEntry _ Pop[]; vp _ Pop[]; oldM: MapEntry _ Map[vp]; * newM.realPage _ oldM.realPage; Map[vp] _ newM; Push[oldM]; *----------------------------------------------------------- * Read current real page number from map. * Note that all we care about are the page number and the vacant indication, * which cannot be influenced either by concurrent IFU or I/O activity or by * the contents of the cache flags. Therefore it is not necessary to flush * the cache or turn tasking off while reading the map. T_ MD, StkP-2; T_ Stack&+1, Call[SetBRForPage]; * Returns RTemp0=0 RMap_ RTemp0, SCall[TranslateMapEntry]; * Returns map entry in T * +1 return: entry is vacant, just return "vacant" and don't set new flags. Stack-1_ T, Branch[AssocExit]; * +2 return: write the map with new flags and old real page number. T_ RCY[T, Stack&-1, 14]; * Combine new flags with old page T_ LCY[T, T, 14], Call[WriteMapPage]; * The pipe now contains the PREVIOUS contents of the map entry just written. * Tasking is off if came from GetFlags. SetFExit: TaskingOn, Call[TranslateMapEntry]; Stack_ T, Branch[AssocExit], DispTable[1, 1, 1]; * Always return here *----------------------------------------------------------- GetFlags: MiscTable[16], * vp _ Pop[]; Push[Map[vp]]; *----------------------------------------------------------- Nop; StkP-1, Call[SetBRForPage]; * Flush this page from the cache so that the map flags are updated. * Note: in principle it should not be necessary to flush twice or to * turn tasking off; but in fact a single flush with tasking on * seems insufficient to capture the dirty bit reliably. Call[FlushPage]; * Returns RTemp0=0, TaskingOff * Read and translate map entry. RMap_ RTemp0, Branch[SetFExit]; * Map-related subroutines *----------------------------------------------------------- SetBRForPage: * Enter: T=virtual page * Exit: T unchanged * MemBase=LPtr, LPtr=VA of virtual page * RTemp0=0 *----------------------------------------------------------- Subroutine; MemBase_ LPtr; RTemp0_ LSH[T, 10]; * set up MemBase and BR BRLo_ RTemp0; RTemp0_ RSH[T, 10]; BRHi_ RTemp0, RTemp0_ A0, Return; *----------------------------------------------------------- FlushPage: * Flushes one page from cache with tasking off. This is done to maintain consistency * between cache and real memory when the map is about to change. * Enter: MemBase=LPtr, LPtr=VA of base of page * Exit: RTemp0=0 * Tasking off, IFU reset (to ensure that activity of the IFU and of the * other tasks will not bring new munches into the cache) * Clobbers RTemp0, Cnt *----------------------------------------------------------- Subroutine; * Do the flush twice, once with TaskingOn and again with TaskingOff. * The idea is that all the actual flushing of dirty munches will occur * with TaskingOn; however, it is logically necessary to do it again with * TaskingOff because in the meantime an I/O task might have touched the * page we are flushing, and subsequent Map operations depend on the page being * completely flushed. IFUReset; RTemp0_ A0, Cnt_ 17S, B_ MD; * Assume 20b munches per page RTemp0_ Flush_ RTemp0, Carry20, Branch[., Cnt#0&-1]; RTemp0_ A0, Cnt_ 16S; TaskingOff; RTemp0_ Flush_ RTemp0, Carry20, Branch[., Cnt#0&-1]; Flush_ RTemp0, RTemp0_ A0, Return; *----------------------------------------------------------- WriteMapPage: * Enter: T = map flags and real page number in Mesa format * MemBase = LPtr, LPtr contains virtual address * Exit: Map written with new value * Pipe contains PREVIOUS contents of map entry * Clobbers T, Q, RTemp0, RTemp1, Cnt *----------------------------------------------------------- Subroutine; * Shift wProtect and dirty bits into position for the hardware, and * test for the combination wProtect & dirty & ref. * Mesa format is B1=wProtect, B2=dirty, B3=ref. * Hardware format for writing is B0=wProtect, B1=dirty (ref can't be set). RTemp1_ NOT T, Q_ Link; TopLevel; T_ T AND (MesaF&P.pageMask); RTemp1_ (RTemp1) AND (MesaF&P.flagsMask); RTemp1_ (NOT (RTemp1)) LSH 1, Branch[.+3, ALU#0]; * This is the state wProtect & dirty & ref, which the Dorado hardware * can't handle (it would mistakenly interpret it as vacant). * Turn off the dirty bit, and set the sign bit in the real page number, * which we have taken over as a duplicate dirty bit. RTemp1_ (RTemp1) AND NOT (LShift[MesaF&P.dirty!, 1]C); T_ T OR (100000C); * Note: RTemp1 was carefully masked (above) so as not to select TIOA values * in [10..17], which can screw up the disk controller! TIOA_ RTemp1; * Set up flags for Map_ Call[FlushPage]; * Returns with TaskingOff; doesn't clobber T * Now write the map entry; T contains the new real page number. Map_ 0S, MapBuf_ T; * Write map entry (real page & flags) PD_ T-T-1, TaskingOn; PD_ PRef, Branch[., ALU<0]; * Wait for map reference to finish * Writing the map zeroed the ref bit. If we desire to set ref, do so by * issuing a PreFetch to the page. Note: this does NOT clobber the pipe, * because PreFetch goes to the ring buffer part, not the private emulator entry. PD_ (RTemp1) AND (LShift[MesaF&P.ref!, 1]C); T_ A0, Link_ Q, Branch[.+2, ALU=0]; Subroutine; PreFetch_ 0S; TIOA_ T, Return; * TIOA=0 required by Mesa emulator *----------------------------------------------------------- TranslateMapEntry: * Translates result of last map reference (Map_ or RMap_) to Mesa format. * This procedure first waits for that map reference to finish. * Enter: MemBase = LPtr, LPtr contains virtual address * Call: SCall[TranslateMapEntry] * Exit: Returns to caller+1 if entry is vacant, caller+2 otherwise. * T = map flags and real page number in Mesa format * Clobbers RTemp0 *----------------------------------------------------------- Subroutine; PD_ PRef, Global; * Subroutine entry instruction T_ NOT (Map'), Branch[.+2, ALU>=0]; * Read previous real page from Pipe PD_ PRef, Branch[.-1]; * Convert hardware flags to Mesa format. * The hardware returns the flags as B0=ref, B2=wProtect, B3=dirty, but * Mesa wants to see them in the form B1=WP, B2=dirty, B3=ref. RTemp0_ Errors', Branch[.+2, ALU>=0]; * Previous flags (complemented) * Transfer the duplicate dirty bit from the real page to the flags T_ T XOR (Or[100000, MesaF&P.dirty!]C), Branch[RealPageInRange]; * Crock for Alto/Mesa and pre-Trinity Pilot: * If real page > 7777B (the highest that can be represented in a MapEntry) * then return Vacant. This compensates for the fact that the software's * initial real memory scan doesn't have an end test! PD_ T AND NOT (MesaF&P.pageMask); Branch[RealPageInRange, ALU=0]; :If[Not[AltoMode]]; ******** PrincOps version ******** * For Pilot, actually change the map entry to be vacant. This is so that * references to that page will fault. (Not sure whether this really matters.) RTemp0_ 140000C; * wProtect & dirty RTemp0_ A0, TIOA_ RTemp0; PD_ (Map_ RTemp0)-1, MapBuf_ RTemp0; PD_ PRef, Branch[., ALU<0]; TIOA_ RTemp0; :EndIf; ********************************** T_ (Or[MesaF&P.wProtect!, MesaF&P.dirty!]C), Return; * Say it is vacant * The following instruction zeroes Carry. It must be the last arithmetic * instruction in ReadMapPage. Note: flags are still complemented. RealPageInRange: RTemp0_ (A_ RTemp0) LSH 1; * Shift wProtect&dirty to Mesa format RTemp0_ (RTemp0) AND (MesaF&P.wProtect&dirty), Branch[.+2, ALU<0]; * Branch if not ref * Uncomplement the wProtect and dirty flags, and set ref if appropriate. RTemp0_ (RTemp0) XOR (Or[MesaF&P.wProtect&dirty!, MesaF&P.ref!]C), DblBranch[MapVacant, MapNotVacant, ALU=0]; RTemp0_ (RTemp0) XOR (MesaF&P.wProtect&dirty), DblBranch[MapVacant, MapNotVacant, ALU=0]; :If[AltoMode]; ********** Alto version ********** * Alto/Mesa wants to see real page = 0 if vacant. MapVacant: T_ MesaF&P.wProtect&dirty, Return; * Vacant, return +1 with real page = 0 :Else; ******** PrincOps version ******** * PrincOps real page is undefined if vacant; however, the Cedar Nucleus depends * on being able to read and write the real page number of vacant entries. MapVacant: T_ T OR (MesaF&P.wProtect&dirty), Return; * Vacant, return +1 :EndIf; ********************************** MapNotVacant: T_ T OR (RTemp0), Return[Carry']; * Not vacant, return +2 TopLevel; *----------------------------------------------------------- InputM: MiscTable[5], * device _ Pop[]; Push[Input[device]]; * Dorado-only feature: if bit 0 of device is on, IOB parity checking is disabled. *----------------------------------------------------------- T_ LSH[T, 10], StkP-1; T_ A0, TIOA_ T, Stack, Branch[.+2, R<0]; Stack_ Input, Branch[MesaIOTail]; Stack_ InputNoPE, Branch[MesaIOTail]; *----------------------------------------------------------- OutputM: MiscTable[6], * device _ Pop[]; data _ Pop; Output[device, data]; *----------------------------------------------------------- T_ LSH[T, 10], StkP-2; T_ A0, TIOA_ T; Output_ Stack&-1; MesaIOTail: TIOA_ T, IFUNext0; * Know T=0 here :If[Not[AltoMode]]; ******** PrincOps version ******** *----------------------------------------------------------- SetMaintPanel: MiscTable[10], * maintPanel _ Pop[]; * Also generate an Opcode trap iff there is a trap handler set up, * so the software has a chance to look at the MP code. *----------------------------------------------------------- MemBase_ SD; Fetch_ Add[sUnimplemented!]S; PD_ MD, StkP-2; MaintPanel_ T, Branch[.+2, ALU#0]; IFUNext0; T_ A0, Branch[OpcodeTrap]; :EndIf; ********************************** *----------------------------------------------------------- RClockM: MiscTable[11], * PushLong[clock]; *----------------------------------------------------------- RBase_ RBase[RTClock]; T_ RTClock, TaskingOff; * Low part -- read atomically!! Stack&+1_ T; T_ RTC430, TaskingOn, Branch[PushT]; * High part KnowRBase[RTemp0]; *----------------------------------------------------------- GenIOin: MiscTable[12], * Push[PrinterIn[]]; *----------------------------------------------------------- StackT_ NOT (EventCntA'), IFUNext2; *----------------------------------------------------------- GenIOout: MiscTable[13], * PrinterOut[Pop[]]; *----------------------------------------------------------- EventCntB_ T, StkP-2, IFUNext0; *----------------------------------------------------------- Checksum: MiscTable[7], * DO * p: LONG POINTER _ PopLong[]; c: CARDINAL _ Pop[]; s: WORD _ Pop[]; * IF c=0 THEN EXIT; * s _ OnesComplementAddAndLeftCycle[s, Fetch[p]^]; * Push[s]; Push[c-1]; PushLong[p+1]; * IF InterruptPending[] THEN GOTO Suspend; * REPEAT Suspend => PC _ savePC; * ENDLOOP; * IF s=-1 THEN s_0; -- turn ones-complement -0 into +0 * Push[s]; *----------------------------------------------------------- Nop; RTemp0_ A0, MemBase_ LPtr; BRHi_ T, StkP-2; * Pop the long pointer into LPtr BRLo_ Stack&-1; * Come here once per munch. RTemp0 contains LPtr-relative address. * StkP addresses c (count of words remaining). * On the first iteration, checksum ((c-1) mod 20b) +1 words; on subsequent * iterations, checksum 20b words. Note that on subsequent iterations, * c mod 20b = 0, so ((c-1) mod 20b) +1 = 20b. CSMunch: T_ (Stack&-1)-1; * A-1 generates carry iff A#0 T_ T AND (17C), Branch[CSDone, Carry']; * Touch the first and last words to be checksummed in this block, * and issue a PreFetch for the next block. T = word count -1. T_ (Fetch_ RTemp0)+(Q_ T), Branch[CSInterrupt, Reschedule]; T_ (Fetch_ T)+(20C); PreFetch_ T, T_ Stack&+1, Stack&+1_ MD; * All possible faults have happened by this point. Stack&+1_ (Stack&+1)-(Cnt_ Q)-1; * Update word count RTemp0_ (Fetch_ RTemp0)+1; Stack&+1_ (Stack&+1)+Q+1; * Update long pointer on stack Stack&-2_ A_ Stack&-2, XorSavedCarry; * Inner loop: 3 instructions per word. T has partial sum, StkP adresses c. CSWordLoop: T_ T+MD, StkP-1, Branch[CSWordExit, Cnt=0&-1]; RTemp0_ (Fetch_ RTemp0)+1, Branch[.+2, Carry]; CSAddNoCarry: * ALU=0 iff came from CSWordExit Stack&+1_ T_ T LCY 1, DblBranch[CSWordLoop, CSMunch, ALU#0]; CSAddCarry: Stack&+1_ T_ (T+1) LCY 1, DblBranch[CSWordLoop, CSMunch, ALU#0]; CSWordExit: PD_ A0, DblBranch[CSAddCarry, CSAddNoCarry, Carry]; * Here when c=0. If result is -0, change it to +0. StkP addresses s. CSDone: PD_ (Stack)+1; * Carry iff sum=177777 StackT_ A_ StackT, XorSavedCarry, IFUNext2; CSInterrupt: StkP+3, Branch[BLTInterrupt]; % ********* De-implemented code ********** *----------------------------------------------------------- WMDS: MiscTable[15], * Write MDS * This opcode sets the high bits of MDS. It supports the execution * IME system code on the Dorado. The idea is to provide IME with a * way of switching whole "banks" of memory very quickly. This opcode * touches all the base registers. The Mesa software must assure that * IO devices are quiescent. This opcode affects the way IO devices * work as well as the way the mesa emulator works. * The MESA instruction, WMDS, pops the new MDSBase from the current top * of the Stack. Then it calls the subroutine, SetMDS to do the work. * WMDS does NOT switch the code base. * The NOVA instruction, WMDS, takes the new MDSBase from AC0 and calls * SetMDS to do the work. WMDS switches the code base also. * SetMDS: * ENTER w/ T= new MDS base, RBase=RBase[EmuBRHiReg]. * CLOBBER T, ETemp1, ETemp2, EmuBRHiReg, ALL BRHi * registers and MemBase. *----------------------------------------------------------- StkP-2, RBase_ RBase[EmuBRHiReg], Call[SetMDS]; T_ (ID)-(PCX')-1, Branch[SetPCAndJump0]; WMDSNova: Nop, At[sd400, 22]; T_ Stack, Call[SetMDS]; Branch[AEmuNext]; Subroutine; KnowRBase[EmuBRHiReg]; SetMDS: * We'll compute a new MDS offset for BRHi based upon (newMDSHi-EmuBRHiReg). T_ T-(EmuBRHiReg); * EmuBRHiReg_ new MDS, T_ difference EmuBRHiReg_ (EmuBRHiReg)+T; ETemp2_ Lshift[36, 10]C; * set MemBase[0..36B],leave CODE alone SetMDSL: MemBase_ ETemp2; DummyRef_ 0S, B_ MD; ETemp1_ VAHi; * capture hi order bits of current BR ETemp1_ (ETemp1)+T; * this is the new value to use ETemp2_ (ETemp2)-(400C); BRHi_ ETemp1, Branch[SetMDSL, ALU>=0]; Q_ Link; TopLevel; * Call SetDisplayBRHi; it will return. Note Link_ overrides implied Call. T_ EmuBRHiReg, RBase_ RBase[RTemp0]; MDSHi_ T, Link_ Q, Branch[SetDisplayBRHi]; % ********* End of de-implemented code ********** % ********* De-implemented code ********** *----------------------------------------------------------- XferL: MiscTable[14], * Long Xfer (MDS switch) * StoreMDS[@LocalBase[L].pc]^ _ PC; * newMDS _ Pop[]; destLink _ Pop[]; Push[L]; Push[LOOPHOLE[MDS, Long].high]; * LOOPHOLE[MDS, Long].high _ newMDS; * XFER[src: L, dst: destLink]; *----------------------------------------------------------- StkP-2; DLink_ Stack, Call[SavePCInFrameIL]; * DLink_ destination link T_ SLink; * SLink=L Stack&+1_ T, RBase_ RBase[EmuBRHiReg]; * save L in Stack T_ EmuBRHiReg; Stack_ T, Q_ Stack; * Stack_ mds, Q_ newMDS T_ Q, Call[SetMDS]; * switch MDS bases RBase_ RBase[RTemp0]; MemBase_ MDS, Branch[Xfer]; * Now do Xfer in new MDSbase % ********* End of de-implemented code ********** *----------------------------------------------------------- LoadRamM: MiscTable[3], * Load Ram and jump * flag _ Pop[]; itemArray: LONG POINTER _ PopLong[]; * nextItem: LONG POINTER _ LoadRam[itemArray+1]; * IF (flag MOD 2)=1 THEN {jump to the start address in the new Ram image}; * PushLong[nextItem]; [] _ PopLong[]; -- leave pointer to next Item above TOS *----------------------------------------------------------- StkP-3, RBase_ RBase[LRFlag]; LRFlag_ NOT T, MemBase_ LPTR; * LoadRam reverses sense of flag * Note: software passes (pointer to first item)-1; must skip over it!!! T_ (Stack&+1)+1; BRLo_ T; T_ A_ Stack&-1, XorSavedCarry; BRHi_ T, Call[LoadRam]; DummyRef_ LRItem, B_ MD; * Convert ending address to long pointer Stack&+1_ VALo; Stack&-2_ VAHi, Branch[AssocExit]; * IFUReset and restart IFU :If[AltoMode]; ********** Alto version ********** *----------------------------------------------------------- SetPartitionM: MiscTable[17], * Set default disk partition number * p: Partition _ Pop[]; * IF p=Partition[0] THEN Push[currentPartition] * ELSE IF p IN [Partition[1]..Partition[maxPartition]] * THEN BEGIN currentPartition _ p; Push[-1]; END ELSE Push[0]; *----------------------------------------------------------- StkP-1, Branch[SetDefaultDiskA]; * Same as Alto instruction :EndIf; ********************************** KnowRBase[RTemp0]; * Memory block zeroing opcodes -- added to instruction set for the benefit of Cedar, * but useful in their own right. *** Someday integrate these with the BLT logic in DMesaRW.mc. But for now: *** *----------------------------------------------------------- LocalBlkZM: MiscTable[100], * Local block zero * count: CARDINAL _ Pop[]; * FOR offset DECREASING IN [0..count) DO StoreMDS[L+offset]^ _ 0; ENDLOOP; * (The implementation must check for interrupts.) *----------------------------------------------------------- T_ (ID)+T+1, MemBase_ L, StkP-1, * (Offset of local 0)-1 (ID=2 here) Branch[BlkZCommon]; *----------------------------------------------------------- LongBlkZM: MiscTable[102], * Long block zero * count: CARDINAL _ Pop[]; * p: LONG POINTER _ PopLong[]; SP _ SP+2; -- leave long pointer on stack * FOR offset DECREASING IN [0..count) DO Store[p+offset]^ _ 0; ENDLOOP; * (The implementation must check for interrupts, and may push the intermediate * count back on the stack, but must not disturb the pointer. This is why * the operation is done in descending order of address.) *----------------------------------------------------------- T_ T-1, MemBase_ LPtr, StkP-2; BRHi_ Stack&-1; BRLo_ Stack&+2; * T = (base-relative) address of last word of block; Stack = count. BlkZCommon: RTemp1_ T-(20C); RTemp0_ T, PreFetch_ RTemp1; * PreFetch 20b words ahead T_ (Stack)-1; T_ T AND (17C), Branch[BlkZDone, Carry']; * Branch if count is zero * On first iteration, do ((count-1) mod 20b)+1 words; * on subsequent iterations, do 20b words. * T = (# words to do this iteration)-1. BlkZMunchEntry: RTemp1_ (RTemp1)-(20C), Branch[.+2, R<0]; PreFetch_ RTemp1; * PreFetch 40b words ahead Cnt_ T, Branch[BlkZInterrupt, Reschedule]; RTemp0_ (Store_ RTemp0)-1, DBuf_ 0C, Branch[.+2, Cnt=0&-1]; BlkZWordLoop: RTemp0_ (Store_ RTemp0)-1, DBuf_ 0C, Branch[BlkZWordLoop, Cnt#0&-1]; Stack_ (Stack)-T-1, T_ MD; * Wait for fault, then update count T_ 17C, Branch[BlkZMunchEntry, ALU#0]; BlkZDone: StkP-1, IFUNext0; BlkZInterrupt: Branch[MesaReschedTrap]; * Event counter and PC sampling stuff. * Also see subroutines in Junk.mc MC[EnableEventsAB, 6000]; MC[DisableEventsAB, 0]; *----------------------------------------------------------- StartCountM: MiscTable[240], * Start Event Counters * control _ Pop[]; ZeroEventCounters[]; InsSetOrEvent[control]; *----------------------------------------------------------- StkP-2, RBase_ RBase[Events], Call[StartCounters]; IFUNext0; *----------------------------------------------------------- ReadCountM: MiscTable[241], * Read Event Counters * CounterValues: TYPE = MACHINE DEPENDENT RECORD * [ * eventALo, eventAHi1, eventAHi0: CARDINAL, -- event counterA * eventBLo, eventBHi1, eventBHi0: CARDINAL, -- event counterB * ] * p: LONG POINTER TO CounterValues _ PopLong[]; ReadCounters[p]; *----------------------------------------------------------- MemBase_ LPtr, StkP-1; BRHi_ Stack&-1; BRLo_ Stack&-1; T_ A0, RBase_ RBase[Events], Call[ReadCounters]; IFUNext0; *----------------------------------------------------------- StopCountM: MiscTable[242], * Stop Event Counters * InsSetOrEvent[disableEventsAB]; *----------------------------------------------------------- T_ DisableEventsAB, StkP-1; InsSetOrEvent_ T, IFUNext0; *----------------------------------------------------------- SetPCHistM: MiscTable[243], * Set PC Sampling Histogram * PCHistogram: TYPE = ARRAY [0..4095] OF LONG CARDINAL; * p: LONG POINTER TO PCHistogram _ PopLong[]; * IF p#NIL THEN EnablePCSampling[p] ELSE DisablePCSampling[]; *----------------------------------------------------------- StkP-2, RBase_ RBase[Events]; Q_ Stack&-1, Call[SetPCHistAddr]; IFUNext0; :If[Not[AltoMode]]; ******** PrincOps version ******** *----------------------------------------------------------- SetIntervalTimerM: MiscTable[255], * Set Interval Timer time *----------------------------------------------------------- StkP-2, RBase_ RBase[WakeupTime]; WakeupTime_ T, IFUNext0; :EndIf; ********************************** * Other Dorado-only instructions KnowRBase[RTemp0]; *----------------------------------------------------------- RWMufManM: MiscTable[246], * Read/write muffler/manifold system * arg: RECORD [useDMD: BOOLEAN, unused: [0..7], dMuxAddr: [0..7777B]]; * result: RECORD [dMuxData: BOOLEAN, unused: [0..77777B]]; * arg _ Pop[]; SetDMuxAddress[arg.dMuxAddr]; * IF arg.useDMD THEN UseDMD[]; * result.dMuxData _ DMuxData[]; Push[result]; *----------------------------------------------------------- StkP-1, Call[SetDMuxAddress]; * Takes address and returns data in T Stack, Branch[.+2, R>=0]; UseDMD; StackT_ T, IFUNext2; :If[Not[AltoMode]]; ******** PrincOps version ******** *----------------------------------------------------------- ResetEtherM: MiscTable[247], * Reset Ethernet hardware and tasks *----------------------------------------------------------- StkP-1, Branch[ResetEther]; :EndIf; ********************************** *----------------------------------------------------------- GetMemConfM: MiscTable[251], * Get memory configuration * Push[realPages]; Push[virtualBanks]; *----------------------------------------------------------- RBase_ RBase[RealPages]; T_ RealPages; Stack&+1_ T; T_ VirtualBanks, Branch[PushT]; *----------------------------------------------------------- HaltM: MiscTable[252], * Halt Dorado, leaving specified value on BMux. * This is useful primarily for power-off: BMux contains time until power-on. * BMux_ Pop; Halt[]; *----------------------------------------------------------- StkP-1, TaskingOff; B_ StackNoUfl, Breakpoint, Branch[.]; *----------------------------------------------------------- SetDisplayFieldRateM: MiscTable[253], * visibleLines _ Pop[]; topBorder _ Pop[]; verticalSync _ Pop[]; * visibleLines is total number of visible lines, including both borders. * All counts are number of scan lines in the even field. *----------------------------------------------------------- StkP-1, Branch[SetDisplayFieldRate]; :If[Not[AltoMode]]; ******** PrincOps version ******** *----------------------------------------------------------- ResetDiskM: MiscTable[254], * Reset disk hardware and tasks *----------------------------------------------------------- StkP-1, Branch[ResetDisk]; :EndIf; ********************************** * Stable Storage block I/O instructions (using GenIn/Out) KnowRBase[RTemp0]; MC[ssbInput, 100000]; MC[ssbClock, 40000]; MC[ssbPowerOn, 10000]; *----------------------------------------------------------- SSBlockIn: MiscTable[256], * Stable Storage block input * DO * c: CARDINAL _ Pop[]; p: LONG POINTER _ PopLong[]; * IF c=0 THEN EXIT; * GenOut[ssbInput+ssbPowerOn+ssbClock]; GenOut[ssbInput+ssbPowerOn]; * Store[p]^ _ GenIn[]; * PushLong[p+1]; Push[c-1]; * IF InterruptPending[] THEN {PC _ savedPC; EXIT}; * ENDLOOP; *----------------------------------------------------------- RTemp0_ A0; RTemp1_ Or[ssbInput!, ssbClock!, ssbPowerOn!]C; RTemp2_ Or[ssbInput!, ssbPowerOn!]C, Call[SSBBlockSetup]; * Control returns here for each munch (or partial munch) to process EventCntB_ RTemp1; * Send ssbClock=1 for first word EventCntB_ RTemp2; * Send ssbClock=0 for first word Nop; * 1-cycle delay required before reading Nop; Nop; Nop; Nop; * The inner loop reads one word from the SSB, issues the clock for the next word, * and exits one word early. This is to ensure adequate delay between sending * the clock and reading the data. SSBInWordLoop: T_ NOT (EventCntA'), * Read current word Branch[SSBInWordExit, Cnt=0&-1]; * Exit if this is the last word EventCntB_ RTemp1; * Send ssbClock=1 for next word EventCntB_ RTemp2; * Send ssbClock=0 for next word Nop; Nop; Nop; Nop; RTemp0_ (Store_ RTemp0)+1, DBuf_ T, * Store current word Branch[SSBInWordLoop]; SSBInWordExit: RTemp0_ (Store_ RTemp0)+1, DBuf_ T, Branch[SSBNextMunch]; *----------------------------------------------------------- SSBlockOut: MiscTable[257], * Stable Storage block output * DO * c: CARDINAL _ Pop[]; p: LONG POINTER _ PopLong[]; word: CARDINAL; * IF c=0 THEN EXIT; * word _ Fetch[p]^; * GenOut[BITOR[word, ssbClock]]; GenOut[word]; * PushLong[p+1]; Push[c-1]; * IF InterruptPending[] THEN {PC _ savedPC; EXIT}; * ENDLOOP; *----------------------------------------------------------- RTemp0_ A0; RTemp1_ NOT (ssbClock); T_ 7000C; * ShC_ [SHA=R, SHB=R, count=16, LMask=1, RMask=16] T_ T OR (341C); ShC_ T, Call[SSBBlockSetup]; * Control returns here for each munch (or partial munch) to process RTemp0_ (Fetch_ RTemp0)+1; * Fetch first word of munch T_ SHMDBothMasks[RTemp1], * Pick up first word and set ssbClock=1 DblBranch[SSBOutWordLoop, SSBOutWordExit, Cnt#0&-1]; * The inner loop fetches one word ahead and exits one word early. * T contains next word to be sent, OR'ed with ssbClock. SSBOutWordLoop: RTemp0_ (Fetch_ RTemp0)+1; * Fetch next word T_ (RTemp1) AND (EventCntB_ T); * Send current word with ssbClock=1, and * set ssbClock to zero T_ SHMDBothMasks[RTemp1], * Pick up next word and set ssbClock=1 EventCntB_ T, * Send current word with ssbClock=0 DblBranch[SSBOutWordLoop, SSBOutWordExit, Cnt#0&-1]; SSBOutWordExit: T_ (RTemp1) AND (EventCntB_ T); * Send final word with ssbClock=1 EventCntB_ T, Branch[SSBNextMunch]; * Send final word with ssbClock=0 *----------------------------------------------------------- SSBBlockSetup: * Enter: RTemp0 = 0 * STK[StkP-1] = word count * STK[StkP-2],,STK[StkP-3] = base pointer * Exit: Exits opcode if no (more) words to transfer or interrupt pending; otherwise: * MemBase = LPtr, containing base pointer * Cnt = number of words to transfer this iteration -1 * Pointer and count updated on stack to account for that number of words * First and last words touched to ensure no faults * Caller should transfer (Cnt)+1 words and increment RTemp0 by that amount, * then branch to SSBNextMunch. Control will return at the instruction after * the initial call to SSBBlockSetup with parameters set up for another munch. * Clobbers T, Q; uses RTemp6 for return link, which must not be clobbered by caller. *----------------------------------------------------------- Subroutine; RTemp6_ Link; TopLevel; MemBase_ LPtr, StkP-2; BRHi_ Stack&-1; * Pop the long pointer into LPtr BRLo_ Stack&+2; * Come here once per munch. RTemp0 contains LPtr-relative address. * StkP addresses c (count of words remaining). * On the first iteration, process ((c-1) mod 20b) +1 words; on subsequent * iterations, process 20b words. Note that on subsequent iterations, * c mod 20b = 0, so ((c-1) mod 20b) +1 = 20b. SSBNextMunch: T_ (Stack)-1; * A-1 generates carry iff A#0 T_ T AND (17C), Branch[SSBDone, Carry']; * Touch the first and last words to be processed in this block, * and issue a PreFetch for the next block. (Reason for touching words is * to ensure that a fault won't occur in the middle of the word loop * while we are wiggling the GenOut clock and such.) T = word count -1. T_ (Fetch_ RTemp0)+(Q_ T), Branch[SSBInterrupt, Reschedule]; T_ (Fetch_ T)+(20C); PreFetch_ T, T_ MD; * All possible faults have happened by this point. Stack&-2_ (Stack&-2)-(Cnt_ Q)-1; * Update word count Stack&+1_ (Stack&+1)+Q+1; * Update long pointer on stack Link_ RTemp6; Subroutine; Stack&+1_ A_ Stack&+1, XorSavedCarry, Return; TopLevel; SSBDone: StkP-3, IFUNext0; SSBInterrupt: Branch[BLTInterrupt];