*-----------------------------------------------------------
Title[PilotDisk.mc...January 27, 1984  5:54 PM...Taft];
* Dorado disk microcode for Pilot
*-----------------------------------------------------------

* This version handles multiple drives.
* It perpetuates the peculiar disk addressing arrangement on drive 0
* (so as to permit the continued coexistence of Alto partitions)
* but uses a conventional arrangement on other drives.

* Drive 0 is assumed to be jumpered for 117 sectors.  Links are installed
* in 6A: 4-11, 5-10; 6B: 2-13, 3-12, 4-11, 5-10, 6-9.
* Other drives are assume to be jumpered for 29 1/3 sectors.  Links are installed
* in 6A: 2-13, 3-12, 6-9, 7-8; 6B: 4-11, 5-10, 6-9.
* The reason for this is that multiple sub-sectors/sector does not work reliably
* with T-300s due to electrical problems in the disk drive that cause
* interference between sector pulses and other status signals.


*-----------------------------------------------------------
* Emulator task -- ResetDisk[mode] instruction
* Resets disk hardware and microcode to initial state, and zaps command chain.
* mode=0 puts microcode in normal state; mode=1 leaves it in a state in which
* it does not execute commands or touch the hardware, but simply dismisses
* every wakeup that occurs.
*-----------------------------------------------------------
Set[XTask, IP[EMU]];
TopLevel;
DontKnowRBase;

ResetDisk:
	TaskingOff, Call[DSKInitPC];
	LdTPC← T, Wakeup[DSK];
	T← Stack&-1, TaskingOn;		* Put parameter where disk task can find it
	KTemp3← T, IFUJump[0];


*-----------------------------------------------------------
* Disk task initialization
*-----------------------------------------------------------
Set[XTask, IP[DSK]];
Subroutine;
DSKInitPC:
	KTemp3← A0;			* Assume init in normal mode
	T← DSK, CoReturn;
TopLevel;

	T← A0, RBase← RBase[DiskRegs],
		Call[ClearDisk];	* Disable controller, clear wakeups
	Call[InitRamPilot];		* Init format Ram
	KTemp3, Branch[KDisable, R odd]; * Test mode flag
	Nop;				* Normal mode
KForgetCmmd:
	T← A0, MemBase← IOBR;
	KTemp0← CSB.next;		* Zero out CSB.next
	Store← KTemp0, DBuf← T, Branch[KNewDrive]; * Select drive 0, enter idle loop

* Task started in disable mode
KDisable:
	T← clearAllTWs;			* Just dismiss all the wakeups
	Output← T, Block, Branch[KDisable];

*-----------------------------------------------------------
* Idle loop awakened once per sector.
* Checks for newly-issued commands.
* MemBase = IOBR
*-----------------------------------------------------------
KIdleLoop:
	T← (KSelect) AND (Not[tagSelectDrive!]C); * Deselect current drive
	Sector, Branch[.+2, R<0];	* Don't deselect if sector unsynchronized
	KPtr← A0, Call[SendDriveTag];
	Block, Call[UpdateSector];

* Here KPtr is odd if drive is currently selected, even if deselected.
KIdleCont:
	T← CSB.next;
	DskMAddr← (Fetch← T)+(Sub[CSB.cylinder!, CSB.next!]C);
	T← clearSeekTagTW, KIOCB← MD,
		Call[DoMuffOutput];	* clear any spurious SeekTagTW

* Interpret IOCB pointer only if it is odd.
	T← (KIOCB)+1, Branch[KIdleLoop, R even];


*-----------------------------------------------------------
* Have a command to execute.
* T = @IOCB.seal, DskMAddr = @CSB.cylinder, KPtr odd iff drive already selected
*-----------------------------------------------------------

	KPtr← (Fetch← T)+1,		* Fetch IOCB.seal
		Branch[.+2, R odd];	* Skip if drive is already selected
	T← KSelect, Call[SendDriveTag];	* Turn on drive select
	KPtr← (Fetch← KPtr)+		* Fetch IOCB.drive
		(Sub[IOCB.command!, IOCB.drive!]C), T← MD;
	KTemp0← T XOR (IOCBSealValue);
	T← (KSelect) AND (tagDriveNumber), * Get currently-selected drive
		Branch[KForgetCmmd, ALU#0]; * Abandon if bad seal
	PD← T#MD, T← MD;		* See if same drive
	KPtr← (Fetch← KPtr)+1,		* Fetch IOCB.command
		Branch[KSameDrive, ALU=0];

* Select new drive; drive number is in T; KTemp0 = 0.
* On drive 0, use subsector count of 3 (4 subsectors/sector).
* On other drives, use subsector count of 0 (1 subsector/sector).
KNewDrive:
	PD← (KTemp0)-T;			* What drive?  Carry← 1 iff T=0
	DskMAddr← CSB.drive, Branch[.+2, Carry'];
	KTemp0← 3C;			* Drive zero, use subsector count 3
	DskMAddr← (Store← DskMAddr)+1, DBuf← T, * Store new drive in CSB.drive
		Call[SetDriveAndSubSector];
	Store← DskMAddr, DBuf← 77777C,	* Don't know current cylinder
		Branch[KIdleLoop];	* Block til index and then try again

* Pick up IOCB.disk address and copy it to IOCB.diskHeader
KSameDrive:
	KCmmd← MD, T← (Fetch← KPtr)+1;	* Fetch IOCB.diskAddress.cylinder
	KCyl← MD, T← (Fetch← T)+1;	* Fetch IOCB.diskAddress.headSector
	KHdSec← MD, T← (Store← T)+1, DBuf← KCyl; * Copy diskAddress to IOCB.diskHeader

* Loop back to here to continue multi-page command.
* DskMAddr = @CSB.cylinder; KCyl and KHdSec already set up; T = @IOCB.diskHeader.sector
KContinueCmmd:
	PD← (KSelect) AND (tagDriveNumber);
	KPtr← (Store← T)+1,		* Leave KPtr = @IOCB.headerPtr
		DBuf← KHdSec,		* Finish copying diskAddress to diskHeader
		Branch[KDrive0, ALU=0];	* Branch if drive 0

* Not drive 0 -- conventional addressing.
	KTemp2← KCyl;			* Just use the real address as specified
	KTemp3← KHdSec, Branch[KCheckSeek];

* Drive 0 -- funny addressing.
* Convert virtual cylinder number (vCyl) to real cylinder (rCyl)
* and head (rHead).  rCyl = vCyl MOD 815; rHead = vCyl / 815 (<19).
* KCyl = vCyl, KHdSec = 0,,vSector (note that vHead is always zero).
* Doing this division efficiently is a problem. Using the standard Dorado algorithm
* is too costly, as it requires a lot of setup and cleanup, including saving
* and restoring the emulator registers Cnt and Q. Instead, go around the following
* 3-instruction loop ceil[log2[19]] = 5 times. The control of the loop depends
* on the fact that nCylinders is odd, so when we shift a bit out of the divisor
* then we are finished..
KDrive0:
	T← HighByte[LShift[nCylinders!, 4]]; * Start with divisor nCylinders * 2↑4
	T← T OR (LowByte[LShift[nCylinders!, 4]]);
	KTemp3← A0;			* Accumulate quotient here
	KTemp2← (KCyl)-T, Branch[.+3];	* Start off by subtracting

KDivSub:
	KTemp2← (KTemp2)-T, Branch[.+2]; * Quotient bit was 1, subtract divisor
KDivAdd:
	KTemp2← (KTemp2)+T;		* Quotient bit was 0, add divisor
	T← RCY[T, T, 1],		* Divisor← divisor/2, low bit to sign
		Branch[.+2, Carry'];	* Test whether we subtracted too much
	 KTemp3← (KTemp3)+(KTemp3)+1,	* No, shift in quotient bit of 1
		DblBranch[KDivSub, KDivDone, ALU>=0];
	KTemp3← (KTemp3)+(KTemp3),	* Yes, shift in quotient bit of 0
		Branch[KDivAdd, ALU>=0];
* If the last quotient bit was 0 then we subtracted too much, so add it back.
	T← LCY[T, T, 1];		* Restore divisor that was used
	KTemp2← (KTemp2)+T;

* Division finished; KTemp3 = quotient (rHead) and KTemp2 = remainder (rCyl).

:If[staggerSectors];	********** Stagger sectors on adjacent cylinders
KDivDone:
* Actual sector ← (desired sector + 8*(cylinder mod 4)) mod nSectors.
* This makes a given sector on consecutive cylinders precess around the disk.
* This means that during sequential transfers, the seek to the next cylinder
* costs only 8 sector times (= ~4.5 ms) rather than an entire revolution (16.66 ms).
* This assumes that the Trident disk's 1-cylinder seek time is less than 4.5 ms;
* it is spec'ed at 6 ms, but measurements show that it is actually about 3 ms.
	T← DPF[KTemp2, 2, 3];		* T← 8*(rCyl mod 4)
	T← (KHdSec)+T;			* Add to desired sector
	PD← T-(nSectors);		* mod nSectors
	T← LSH[T, 10], Branch[.+2, ALU<0];
	T← T-(LShift[nSectors!, 10]C);

:Else;			************************* Not staggering sectors
KDivDone:
	T← LSH[KHdSec, 10];		* rSector,,0
:EndIf;			************************************************
	KTemp3← LCY[T, KTemp3, 10];	* rHead,,rSector

* Now KTemp2 = rCyl, KTemp3 = rHead,,rSector, DskMAddr = @CSB.cylinder.
* See if we have to seek.
KCheckSeek:
	T← Fetch← DskMAddr;		* Fetch CSB.cylinder
	DskMAddr← MD, Store← T, T← DBuf← KCyl; * CSB.cylinder ← vCyl
	PD← (DskMAddr) XOR T,
		Branch[KNoRestore, R>=0]; * Branch if CSB.cylinder >= 0

* Need to do a restore first.
	T← tagControl;
	T← T OR (Or[tagDiskReset!, tagReZero!]C), Call[SendTag];
	T← clearAllTWs, Call[DoMuffOutput];
	TIOA[DiskControl];
	T← blockTilIndex, Call[OutputGetsT];
	Sector← T-T-1, Block;		* Now do a new seek always

KNoRestore:
	Branch[.+2, ALU=0];		* Branch if already at cylinder
	T← KTemp2, Call[SeekAndWaitForReady]; * Seek to rCyl

* Select the head.  KTemp3 = real head,,sector.
* Don't bother to wait for the tag command to complete; we have no more
* tags to issue, and the dangling SeekTagTW will be cleared below.
* This saves about 1.5 microseconds in a time-critical window.
* NOTE: there must be at least 1.2 microseconds' worth of instructions
* between here and the clearing of SeekTagTW below.
	T← RSH[KTemp3, 10];
	T← T OR (tagHead);		* T← head tag command
	PD← KCmmd, TIOA[DiskTag];
	Output← T, Branch[KSectorDone, ALU=0]; * Branch if seek-only command

* Now wait for correct sector
	KTemp3← (KTemp3) AND (377C);	* Extract sector

KWaitSector:
	SCall[WaitForSector];		* Returns with TIOA[DiskControl];
	 Branch[KBadSector];		* +1 return: failed to find sector

*-----------------------------------------------------------
* Issue the command to the controller.
* Then check to see whether we issued it in time, and if not revoke it
* and wait for this sector to come around again.
*-----------------------------------------------------------
	Output← KCmmd, Call[UpdateSector]; * Returns with T = Sector

* Clear dangling SeekTagTW from earlier head tag command, which is
* assumed to have completed by this point.
	KTemp0← clearSeekTagTW;
	Output← KTemp0;
	PD← (KTemp3) XOR T;		* Are we still at the same sector?
	T← A0, TIOA[DiskControl], Branch[KCmmdInTime, ALU=0];

	Output← T;			* Not in time.  This clears Active
	Output← T, Branch[KWaitSector];	* This reloads command register

*-----------------------------------------------------------
* Now do the data transfers.
* Each call to DoDiskBlock executes the command in KCmmd[14:15]
* and left-cycles KCmmd 2 bits.  Note that at the end of all this,
* KCmmd contains its original value.  Any errors that occur are both
* reported in the IOCB and merged into KStatus.
* DoDiskBlock does not return if an error occurs.
*-----------------------------------------------------------
KCmmdInTime:
	KTemp1← sizeHeader;		* Check all words of header
* Must not block until 4th cycle after SeekTagTW was cleared (above)
	KCmmd← RCY[KCmmd, KCmmd, 6],	* Header command to [14:15]
		Block, Call[UpdateSector]; * Block til start of sector

	DskMAddr← Sub[0, sizeHeader!]C, Call[DoDiskBlock];

	KTemp1← Sub[sizeLabel!, 2]C;	* Check all but last 2 words of label
	DskMAddr← Sub[0, sizeLabel!]C, Call[DoDiskBlock];

	KTemp1← sizeData;		* Check all words of data
	DskMAddr← Sub[0, sizeData!]C, Call[DoDiskBlock];
	Nop;

*-----------------------------------------------------------
* All blocks in sector were transferred successfully.
* Update IOCB.pageCount, cylinder, sector, and dataPtr,
* increment the filePageLo field and zero the flags in the label,
* and check for more pages to do.
* KDataLo = BRLo for last block transferred (normally data)
* KDataHi = BRHi for last block +1
* Note: KDataHi,,KDataLo point one beyond the last word transferred!
*-----------------------------------------------------------

KSectorDone:
	T← KIOCB, MemBase← IOBR;
	KPtr← T+(IOCB.diskAddress)+1;	* KPtr← @IOCB.diskAddress.sector
	T← (KHdSec) AND (377C);		* Extract sector just completed
	PD← T#(Sub[nSectors!, 1]C);	* Last sector?
	T← KHdSec← (KHdSec)+1, Branch[KNotLastSector, ALU#0];

* Reached max sector number; reset to zero and decide what to do next.
	PD← (KSelect) AND (tagDriveNumber); * What drive?
	T← KHdSec← (KHdSec) AND (177400C), * Reset sector to 0
		Branch[KDoneNonZero, ALU#0];

* Drive zero: keep head number at zero and increment cylinder.
	KPtr← (Store← KPtr)-1, DBuf← T;	* Store updated sector
	T← KCyl← (KCyl)+1, Branch[KNotLastSector]; * Increment cylinder, go store it

* Not drive zero: just increment head.
* Note that head overflow is not detected here but must be handled by software.
KDoneNonZero:
	KHdSec← T← (KHdSec)+(400C);

* KPtr = @IOCB.diskAddress.sector, T = updated KHdSec; --OR--
* KPtr = @IOCB.diskAddress.cylinder, T = updated KCyl.
KNotLastSector:
	Store← KPtr, DBuf← T;

* Now fix up the copy of the label that is in the IOCB.
* Operation is:
*   IF (IOCB.diskLabel.filePageLo ← IOCB.diskLabel.filePageLo+1)=0 THEN
*     IOCB.diskLabel.filePageHi ← IOCB.diskLabel.filePageHi+1;
*   label.flags ← 0;
	T← (KIOCB)+(Add[IOCB.diskLabel!, Lab.filePageLo!]C);
	T← (Fetch← T)+1;		* Fetch IOCB.diskLabel.filePageLo
	T← (Fetch← T)-1, KTemp0← MD;	* Fetch IOCB.diskLabel.filePageHi
	KTemp0← (KTemp0)+1;		* Increment filePageLo
	T← (Store← T)+1, DBuf← KTemp0, KTemp0← MD, * Store it back
		Branch[.+2, Carry'];
	KTemp0← (KTemp0)+(1000C);	* Carry into filePageHi
	KTemp0← (KTemp0) AND (Not[Lab.fileFlags!]C); * Zero label flags
	Store← T, DBuf← KTemp0;		* Store back Lab.filePageHi

* Now update the data pointer if required.
	KPtr← T← T+(Sub[IOCB.pageCount!, * KPtr← @IOCB.pageCount
		Add[IOCB.diskLabel!, Lab.filePageHi!]]C);
	T← (Fetch← T)+(Sub[IOCB.dataPtr!, IOCB.pageCount!]C),
		KCmmd, Branch[KNoUpdateDataPtr, R>=0]; * Branch if incrementDataPtr=0

	T← (Store← T)+1, DBuf← KDataLo;	* Store updated data ptr
	Store← T, DBuf← KDataHi;

* Now decrement page count and see if there are any more pages to do.
KNoUpdateDataPtr:
	T← (MD)-1;			* Decrement pageCount
	Store← KPtr, DBuf← T,		* Store in IOCB
		Branch[KCmmdDone, ALU=0]; * Branch if pageCount=0

* More to do.  Get back into a good state to continue command for next sector.
	DskMAddr← CSB.cylinder;
	T← (KIOCB)+(IOCB.diskHeader);	* @IOCB.diskHeader.cylinder
	T← (Store← T)+1, DBuf← KCyl,	* Start to store IOCB.diskHeader
		Branch[KContinueCmmd];

* Entirely done with this command.
* Smash its seal with zero and chain to next.
KCmmdDone:
	T← (Fetch← KIOCB)+1;		* Fetch IOCB.next
	Store← T, DBuf← 0C, KIOCB← MD;	* Zero IOCB.seal
KCmmdChain:
	T← CSB.interruptMask;
	T← (Fetch← T)-1;		* Fetch CSB.interruptMask
	Store← T, DBuf← KIOCB;		* Store CSB.next
	KPtr← T-T-1, RBase← RBase[NWW];	* Make KPtr odd
	NWW← (NWW) OR MD, Reschedule;	* Request interrupt(s)
	RBase← RBase[DiskRegs], Branch[KIdleCont]; * Go consider next command


*-----------------------------------------------------------
* If an error occurred, freeze disk activity by making CSB.next even.
* Zero the command register in case the microcode has gotten out of sync
* with the hardware, and reset errors latched in the disk drive.
*-----------------------------------------------------------

KSectorError:
	T← A0, TIOA[DiskControl];
	KIOCB← (KIOCB)+1, Output← T, Call[OutputGetsT];
	T← tagControl;
	T← T OR (tagDiskReset), Call[SendTag];
	T← clearErrors, Call[DoMuffOutput];
	KIOCB← (Store← KIOCB)-1, DBuf← 0C; * Zero the seal
	KIOCB← (KIOCB)-1, Branch[KCmmdChain]; * KIOCB was odd, now even

* If we can't find the desired sector, report a sector number error.
KBadSector:
	T← (KIOCB)+(IOCB.headerStatus);
	Store← T, DBuf← DS.sectorSearchErr, Branch[KSectorError];

*-----------------------------------------------------------
DoDiskBlock:	* Do disk command for one block
* Enter: KCmmd[14:15] = command for this block (Dorado format)
*	KPtr = @IOCB.xxPtr (xx = header, label, data)
*	DskMAddr = -length of block
*	KTemp1 = words to check (if checking; remainder are read)
*	MemBase = IOBR
* Exit:	KCmmd left-cycled 2 bits
*	KStatus = status for block
*	KDataLo, KDataHi = LONG POINTER to last word of block +1
*	MemBase = IOBR
* Note: if an error occurs, does not return but rather goes directly
* to KSectorError after storing error status.
* Clobbers T, KTemp0, KTemp1, KTemp2, DskMAddr, KDataLo, KDataHi, DiskBR
*-----------------------------------------------------------
Subroutine;

	KTemp2← Link;
TopLevel;
	KPtr← (Fetch← KPtr)+1;		* Fetch IOCB.xxPtr.low
	KPtr← (Fetch← KPtr)+1, T← MD;	* Fetch IOCB.xxPtr.high
	T← T-(DskMAddr), MemBase← DiskBR; * Point past end of block
	BRLo← T, KDataLo← B← T, T← MD;	* Set BR for negative indexing
	T← T-1, XorSavedCarry;
	BDispatch← KCmmd;		* Dispatch on KCmmd[14:15]
	KDataHi← (BRHi← T)+1;

KCmmdTable: DispTable[4, 7, 4],
	MemBase← IOBR, Branch[KCmmdNone]; * 0 noop
	T← 201C, Branch[KCmmdWrite];	* 1 write; T← sync pattern to write
	KTemp0← muffRdFifoTW, Branch[KCmmdCheck]; * 2 check
	KTemp0← muffRdFifoTW, Branch[KCmmdRead]; * 3 read

* A "no-op" action actually terminates the command; it would be incorrect
* for a command to contain anything besides no-op after no-op.
* Nevertheless, we "perform" each no-op so as to get KCmmd properly cycled
* back to its original position.
KCmmdNone:
	KPtr← (KPtr)+(2C), Branch[KCmmdShift]; * Skip ECC words

*-----------------------------------------------------------
* Write command.
* Controller gives a WriteFifoTW when there is room for at least 4 words
* in the Fifo.  Doing an Output that reduces the free space below 4 causes
* WriteFifoTW to be dropped at T0 of the 4th cycle after the Output,
* so a Block on the 5th cycle will take effect.
* I think it was originally intended that a 3-instruction, 2-word loop
* be possible:			Output; Output; Block;
* Unfortunately, this doesn't work if the second Output causes the wakeup
* to be dropped, because it is dropped so late that we will go around
* the loop twice more, outputting 4 words when there is room for only 3.
* Thus the minimal loop is:	{Output; Output; Nop}; Block;
* where the instructions inside { } may be permuted in any way.
* An equivalent loop is:	Output; Block;
* and it takes less microcode.
* Due to control section bugs, we must not Block on a memory reference
* if the task wakeup might be dropped at T0 of that instruction.
*-----------------------------------------------------------
KCmmdWrite:
	TIOA[DiskData];
	DskMAddr← (Fetch← DskMAddr)+1, Output← T; * Output sync pattern

	DskMAddr← (Fetch← DskMAddr)+1, Output← MD;
	Block, Branch[.-1, ALU<0];

	Output← MD;			* Output last word

* Changing TIOA from DiskData to DiskControl disables WriteFifoTW.
* The wakeup is removed at T0 of the third instruction after the one that
* changes TIOA, so the earliest we can block is the fourth instruction.
* Hardware generates one more WriteFifoTW when it is done with this block.
	KStatus← A0, TIOA[DiskControl];
	KTemp0← muffWriteError;		* Select appropriate status bit
	KCmmd← LCY[KCmmd, KCmmd, 2];	* Shift command for next block
	KPtr← (KPtr)+1, MemBase← IOBR;	* Skip over ECC words
	KPtr← (KPtr)+1, Block,		* Wait til write done
		Branch[KCmmdEndBlock];

*-----------------------------------------------------------
* Read command.
* Controller gives a ReadFifoTW when there are at least 3 words in the Fifo
* (actually, 2 in the Fifo and 1 in OutReg).  Doing an Input that reduces
* the count below 3 causes ReadFifoTW to be dropped at T0 of the 4th cycle
* after the Input, so a Block on the 5th cycle will take effect.
* Thus the minimal loop is:	Input; Block;
* Due to control section bugs, we must not Block on a memory reference
* if the task wakeup might be dropped at T0 of that instruction.
*-----------------------------------------------------------
KCmmdRead:
	DskMAddr← (DskMAddr)-1, Block, Call[Read1Muff];
	KTemp0, TIOA[DiskData], Branch[KReadBadTW, R even];
	PD← DskMAddr, T← Input, Branch[.+2]; * Can't do back-to-back Inputs

	PD← (Store← DskMAddr)+1, DBuf← T, T← Input;
	DskMAddr← (DskMAddr)+1, Block, Branch[.-1, ALU#0];

* A read block ends with 2 garbage words and 2 ECC words.  When we fall out
* of the main loop, we have already read the first garbage word.
	KStatus← A0, Call[ReadECC];	* Returns ECC words in KTemp0 and T
	PD← (KTemp0) OR T, MemBase← IOBR,
		Branch[KReadCheckEnd];	* Remainder same as check case

*-----------------------------------------------------------
* Check command.
* Controller gives a ReadFifoTW when there is at least 1 word in the Fifo
* (actually, OutReg full regardless of Fifo).  Doing an Input that empties
* the Fifo causes ReadFifoTW to be dropped at T0 of the 2nd cycle
* after the Input, so a Block on the 3rd cycle will take effect.
* Thus the minimal loop is:	Input; Nop; Nop; Block;
* Due to control section bugs, we must not Block on a memory reference
* if the task wakeup might be dropped at T0 of that instruction.
*-----------------------------------------------------------
KCmmdCheck:
	DskMAddr← (Fetch← DskMAddr)+1, Block, Call[Read1Muff];
	KTemp0, Branch[KCheckBadTW, R even];
	KStatus← A0, TIOA[DiskData];	* No errors seen yet

* Main check loop -- 4 cycles per word.
* At the top of the loop, MD = the word fetched from memory during the
* previous cycle.
KCheckLoop:
	T← Input;
	PD← T XOR MD, DskMAddr, Branch[KCheckLast, R>=0];
	KTemp1← (KTemp1)-1, Branch[KCheckError, ALU#0];
KCheckNext:
	DskMAddr← (Fetch← DskMAddr)+1, Block,
		DblBranch[KCheckLoop, KCheckEnd, ALU#0];

* If a check error occurs, set the check error status bit and then
* stay in the check loop for the rest of the block.  This is so that
* we do NOT clobber the bootChainLink from the last good label.
KCheckError:
	KStatus← DS.checkErr;
	KTemp1← 77777C, Branch[KCheckNext];

* Checking last word of block.
KCheckLast:
	PD← A0, Branch[KNoCheckNext, ALU=0];
	KStatus← DS.checkErr, Branch[KCheckDone];

* Checked all words needing to be checked, and there is at least one
* word to be read.
KCheckEnd:
	DskMAddr← (DskMAddr)-1;

* In this loop we are just reading data, not checking.
KNoCheckLoop:
	T← Input;
	DskMAddr← (Store← DskMAddr)+1, DBuf← T;
KNoCheckNext:
	PD← KStatus, Branch[.+2, ALU>=0];
	Block, Branch[KNoCheckLoop];

* Here when done checking.  KStatus is nonzero if there were any differences.
KCheckDone:
	TIOA[DiskMuff], Branch[.+3, ALU#0];

* No differences: clear CompareErr.  Note that if a compare error occurred
* in an earlier block, ReadDataErr will be set, and this will NOT clear it.
	T← clearCompareErr;
	Output← T;

* Now continue on and read the ECC.
	TIOA[DiskData], Block;
	KStatus← A0, MemBase← IOBR, Call[CheckECC];

* Tail of both Read and Check commands.

* At this point, the ECC words are in T and KTemp0.
* ALU = (KTemp0) OR T.
* KPtr points to first ECC word for this block.
KReadCheckEnd:
	T← (Store← KPtr)+1, DBuf← T, Branch[.+2, ALU=0]; * Store ECC0
	KStatus← (KStatus) OR (DS.eccErr); * Set error status
	KPtr← (Store← T)+1, DBuf← KTemp0; * Store ECC1
KCmmdShift:
	KCmmd← LCY[KCmmd, KCmmd, 2];	* Shift command for next block
	KTemp0← muffReadError, Branch[KCmmdEndBlock];

* If a non-Fifo TW occurs at the beginning of reading or checking, most
* likely the data was so bad that the controller was unable to lock onto it
* before reaching the end of the sector.  Report this as a SectorOverflow.
KReadBadTW:
	Nop;
KCheckBadTW:
	KStatus← DS.sectorOvfl;		* Post this status
	KTemp0← T← A0;			* So we won't post an ECC error
	KCmmd← A0, MemBase← IOBR, Branch[KReadCheckEnd];

*-----------------------------------------------------------
* End of transfer for block.  Check for hardware errors and store status.
* KStatus = microcode status for this block
* KTemp0 = muffReadError or muffWriteError.
* KPtr = @IOCB.xxStatus,
* MemBase = IOBR
*-----------------------------------------------------------
KCmmdEndBlock:
	Call[Read1Muff];		* Read status summary bit
	KTemp0← muffsStatus, Branch[KNoHdwErr, R even];
	T← KTemp0, Call[Read20Muffs];	* Read complete status word
	T← T AND (Not[Or[DS.eccErr!, DS.sectorSearchErr!]]C);

* T = 0 here if there was no hardware error
KNoHdwErr:
	KStatus← T← (KStatus) OR T;
	Store← KPtr, PD← DBuf← T;
	Link← KTemp2, Branch[KSectorError, ALU#0];
Subroutine;
	KPtr← (KPtr)+1, Return;

*-----------------------------------------------------------
InitRamPilot:		* Init format Ram for Pilot.
* Also sets subsector count for drive 0 and issues a BlockTilIndex.
* Enter:
* Exit: TIOA[DiskMuff]
* Clobbers T, KTemp0, KTemp1, KTemp2
*-----------------------------------------------------------
Subroutine;

	KTemp2← Link;
TopLevel;
	MaxSectors← 36C;		* 30 sectors around (actually, 29 +
					* a fraction, though we use only 28)
	KTemp0← 3C;			* 4 subsectors per sector
	KSelect← (KSelect) OR (4000C);	* Sectors do not evenly divide the disk
	T← A0, Call[SetDriveAndSubSector]; * Drive 0
	TIOA[DiskRam];
	T← Sub[sizeHeader!, 1]C, Call[OutputGetsT]; * [0] header count - 1
	T← Sub[sizeLabel!, 1]C, Call[OutputGetsT]; * [1] label count - 1
	T← Sub[sizeData!, 1]C;
	T← A0, Output← T,		* [2] data count - 1
		Call[OutputGetsT];	* [3] count for unused block = 0
	T← 104C, Call[OutputGetsT];	* [4] control tag for read
	T← 204C, Call[OutputGetsT];	* [5] control tag for write
	T← 4C;
	T← A0, Output← T,		* [6] control tag for head select
		Call[OutputGetsT];	* [7] control tag to zero the tag bus
	T← 33C, Call[OutputGetsT];	* [10] write delay first block
	T← 6C, Call[OutputGetsT];	* [11] write delay succeeding blocks
	T← 11C, Call[OutputGetsT];	* [12] read delay first block
	T← 2C, Call[OutputGetsT];	* [13] read delay succeeding blocks
	T← T-1, Output← T;		* [14] head select delay = 2
	T← A0, Output← T;		* [15] no. of ECC words - 1 = 1
	Output← T,			* [16] the constant 0
		Call[OutputGetsT];	* [17] unused word
	T← clearAll;			* Clear all TWs and errors
	Link← KTemp2, Branch[DoMuffOutput]; * Do it and return