*----------------------------------------------------------- Title[DMesaMiscOps.mc...May 4, 1983 6:10 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) Set flags and associate subroutines FlushPage Remove the virtual page from the cache WriteMapPage Write virtual page % 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; *----------------------------------------------------------- * First, flush virtual page from cache. * Must reset IFU to prevent it from possibly making references to the * page being flushed. FlushPage turns tasking off for the same reason. T← MD, StkP-2; T← Stack&+1, IFUReset, Call[SetBRAndFlushPage]; * Returns with TaskingOff * Store new flags and real page into map. T← Stack&-2, Call[WriteMapPage]; * Returns with TaskingOn * Restart IFU, since we reset it above. 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 T← MD, StkP-2; T← Stack, IFUReset, Call[SetBRAndFlushPage]; * Required to validate map flags RTemp0← A0, SCall[ReadMapPage]; * +1 return: entry is vacant, just return old flags and don't set new ones Stack← T, TaskingOn, Branch[AssocExit]; * +2 return: write the map with new flags and old real page number. Stack&+1← T; * Old value to return T← RCY[T, Stack&-1, 14]; * Combine new flags with old page T← LCY[T, T, 14], Call[WriteMapPage]; * Returns with TaskingOn Branch[AssocExit]; *----------------------------------------------------------- GetFlags: MiscTable[16], * vp ← Pop[]; Push[Map[vp]]; *----------------------------------------------------------- T← MD, StkP-1; T← Stack, IFUReset, Call[SetBRAndFlushPage]; * Required to validate map flags RTemp0← A0, Call[ReadMapPage]; Stack← T, TaskingOn, Branch[AssocExit], DispTable[1, 1, 1]; * Always return here *----------------------------------------------------------- SetBRAndFlushPage: * Enter * T=virtual page * Exit * T unchanged * MemBase=LPtr, LPtr=VA of virtual page * RTemp0=0 * TaskingOff * Clobbers RTemp0, Cnt *----------------------------------------------------------- Subroutine; MemBase← LPtr; RTemp0← LSH[T, 10]; * set up MemBase and BR BRLo← RTemp0; RTemp0← RSH[T, 10]; BRHi← RTemp0; * 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 a higher-priority task might have touched the * page we are flushing, and subsequent Map operations depend on the page being * completely flushed. 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 * TaskingOff * Exit: TaskingOn * Clobbers T, RTemp0 *----------------------------------------------------------- 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). RTemp0← NOT T; T← T AND (MesaF&P.pageMask); RTemp0← (RTemp0) AND (MesaF&P.flagsMask); RTemp0← (NOT (RTemp0)) 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. RTemp0← (RTemp0) AND NOT (LShift[MesaF&P.dirty!, 1]C); T← T OR (100000C); * Now write the map entry. * Note: RTemp0 was carefully masked (above) so as not to select TIOA values * in [10..17], which can screw up the disk controller! TIOA← RTemp0; * Set up flags for Map← TaskingOn; * Will take after next instruction PD← (Map← 0S)-1, MapBuf← T; * Write map entry (real page & flags) 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. PD← (RTemp0) AND (LShift[MesaF&P.ref!, 1]C); T← A0, Branch[.+2, ALU=0]; PreFetch← 0S; TIOA← T, Return; * TIOA=0 required by Mesa emulator *----------------------------------------------------------- ReadMapPage: * Enter: MemBase = LPtr, LPtr contains virtual address * RTemp0 = 0 * Call: SCall[ReadMapPage] * 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; RMap← RTemp0; * Read map entry (RTemp0=0) PD← PRef; * Wait for map reference to finish T← NOT (Map'), Branch[.-1, ALU<0]; * Read previous real page from Pipe * 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; Branch[MiscOpcodeTrap]; :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]; *----------------------------------------------------------- PD← T, StkP-1, RBase← RBase[DefaultDisk]; PD← T-(6C), Branch[.+2, ALU#0]; T← DefaultDisk, Branch[PushT]; * Return current default T← T-(Q← T)-1, Branch[.+2, Carry']; T← A0, Branch[PushT]; * Illegal, return 0 DefaultDisk← Q, Branch[PushT]; * Legal, set it and return -1 :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 *----------------------------------------------------------- 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; **********************************