{
File name bbSubs.mc
Last edited by Jim Frandeen: January 12, 1982 4:18 PM: Reverse labels at SLRBack+1 and DLRBack+1.
Last edited by Jim Frandeen: January 11, 1982 1:35 PM: Fix at 3,4,mapSFixes.
Sandman: January 8, 1982 11:03 AM: init rhVS(VD) from uReg in Src(Dst)VAMod.
Last edited by Jim Frandeen: August 20, 1981 2:18 PM: Change for new Assembler.
Last edited by Jim Frandeen: March 16, 1981 3:52 PM: Change MoverhVtoStkandRestore to fix bug for crossing 64K boundaries.
Last edited by Jim Frandeen: March 15, 1981 11:05 PM: Add entry points to RestoreRandRHRegs and rearrange for new Block.mc that includes Checksum.
Last edited by Don Charnley: February 26, 1981 2:39 PM: Make MoverhVToStkandRestore smaller for new stack size.
Last edited by Jim Frandeen: February 24, 1981 8:46 PM: Add entry points to RestoreRandRHRegs and rearrange for new Block.mc.
Created by: Don Charnley January, 1980
Description: BitBlt op-code
}
{——————————————————————————————————————————————————————
dT SUBROUTINE
first cycle = c* , one cycle long
This subroutine is used to aid in loading a link register.
REGISTERS
rLvalue to place in link register
Lxlink register to be loaded
CALLING SEQUENCE
To load a link register
[] ← rL, YDisp,c2;
[] ← retnum, Lx ← 0, XDisp, DISP4[dT],c3;
{rtn here}Noop,c2, at[retnum,10,dTrets];
RETURNS THRU
dTRets
——————————————————————————————————————————————————————}
dT:
{0}RET[dTRets],c*, at[0,10,dT];
{1}RET[dTRets],c*, at[1,10,dT];
{2}RET[dTRets],c*, at[2,10,dT];
{3}RET[dTRets],c*, at[3,10,dT];
{4}RET[dTRets],c*, at[4,10,dT];
{5}RET[dTRets],c*, at[5,10,dT];
{6}RET[dTRets],c*, at[6,10,dT];
{7}RET[dTRets],c*, at[7,10,dT];
{8}RET[dTRets],c*, at[8,10,dT];
{9}RET[dTRets],c*, at[9,10,dT];
{0A}RET[dTRets],c*, at[0A,10,dT];
{0B}RET[dTRets],c*, at[0B,10,dT];
{0C}RET[dTRets],c*, at[0C,10,dT];
{0D}RET[dTRets],c*, at[0D,10,dT];
{0E}RET[dTRets],c*, at[0E,10,dT];
{0F}RET[dTRets],c*, at[0F,10,dT];
{——————————————————————————————————————————————————————
MoverhVToStkandRestore SUBROUTINE
length = 3 clicks
This subroutine is used to move the rhV registers into the stack.
USES
L0caller
MOVES
Rbb1to UDstBit
Qto USrcBit
EXITS TO RestoreRandRHRegs SUBROUTINE
——————————————————————————————————————————————————————}
MoverhVToStkandRestore:
rhL ← UrhLsave, GOTO[RestoreBlockRegsC3],,c*{c1}, at[3,8,MoverhVToStkandRestore];
{——————————————————————————————————————————————————————
RestoreRandRHRegs SUBROUTINE
length = 2 1/3 clicks
This subroutine is used to restore the R registers and rh registers which were saved at the entry into BitBlt.
USES
L0caller
RESTORES
Lfrom ULsave
Gfrom UGsave
PCfrom UPCsave
rhMDSfrom UrhMDSsave
rhPCfrom UrhPCsave
rhGfrom UrhGsave
rhLfrom UrhLsave
RETURNS THRU
RestoreCallers
RestoreBlockRegs entries are used by Block.mc in order to end up on the right cycle.
Block.mc saves all registers but does not use them all.
——————————————————————————————————————————————————————}
RestoreRandRHRegs:
rhL ← UrhLsave,c*{c1}, at[2,8, LSEPReturn];
RestoreBlockRegsC3:
rhPC ← UrhPCsave,c*{c2};
RestoreBlockRegsC2:
rhMDS ← UrhMDSsave,c*{c3};
RestoreBlockRegsC1:
rhG ← UrhGsave,c*{c1};
RestoreBlockRegsC3Initial:
{This entry can be used from Block only if rhG has not yet been modified.}
PC ← UPCsave,c*{c2};
G ← UGsave, L0Disp,c*{c3};
L ← ULsave, RET[RestoreCallers],c*{c1};
{——————————————————————————————————————————————————————
DstVAMod SUBROUTINE
first cycle = c3 , last cycle = c2
Timing: 4 clicks, + 1 if neg, + 1 if rh fix
This subroutine is used to modify the destination virtual address.
CALLING ARGUMENTS
rhWhocaller
TempBplincrement for the destination address
UDstVALovirtual destination page and word
UDstBitvirtual destination bit
rhDstVAvirtual destination rh
always UPDATES
UDstVALovirtual destination page and word
UDstBitvirtual destination bit
rhDstVAvirtual destination rh
USES
Qvirtual page and word
TempBbit
rhRetto call VAModSub
CALLS
VAModSub
RETURNS THRU
DstVAModRtn
——————————————————————————————————————————————————————}
DstVAMod:Noop,c*{c1};
Noop,c*{c2};
rhVD ← UrhVD,c*{c3};
Q ← UDstVALo,c*{c1};
TempB ← UDstBit,c*{c2};
rhRet ← VAaRet, CALL[VAMod],c*{c3};
{VAMod subroutine here {2 or 3 clicks},c*{c1}-c*{c3};}
{return here if rh needs fix}
VD ← UrhVD,c*{c1}, at[Or[VAaRet,1],8,VAModRet];
VD ← VD + TempBpl,c*{c2};
UrhVD ← VD,c*{c3};
Noop,c*{c1};
fixrhVD:[] ← rhRet, XDisp,c*{c2};
rhVD ← VD LRot0, DISP3{RET}[VAModRet],c*{c3};
{return here if no rh fix or after rh fix}
UDstVALo ← Q,c*{c1}, at[VAaRet,8,VAModRet];
DstVAExit:[] ← rhWho, XDisp,c*{c2};
UDstBit ← TempB, DISP2{RET}[DstVAModRet],c*{c3};
{——————————————————————————————————————————————————————
SrcVAMod SUBROUTINE
first cycle = c3 , last cycle = c2
Timing: 4 clicks, + 1 if neg, + 1 if rh fix
This subroutine is used to modify the source virtual address.
CALLING ARGUMENTS
rhWhocaller
TempBplincrement for the source address
USrcVALovirtual source page and word
USrcBitvirtual source bit
rhSrcVAvirtual source rh
always UPDATES
USrcVALovirtual source page and word
USrcBitvirtual source bit
rhSrcVAvirtual source rh
USES
Qvirtual page and word
TempBbit
rhRetto call VAModSub and SrcRemap
CALLS
VAModSub
RETURNS THRU
SrcVAModRtn
——————————————————————————————————————————————————————}
SrcVAMod:Noop,c*{c1};
Noop,c*{c2};
rhVS ← UrhVS,c*{c3};
Q ← USrcVALo,c*{c1};
TempB ← USrcBit,c*{c2};
rhRet ← VAbRet, CALL[VAMod],c*{c3};
{VAMod subroutine here {2 or 3 clicks},c*{c1}-c*{c3};}
{return here if rh needs fix}
VS ← UrhVS,c*{c1}, at[Or[VAbRet,1],8,VAModRet];
VS ← VS + TempBpl,c*{c2};
UrhVS ← VS,c*{c3};
Noop,c*{c1};
fixrhVS:[] ← rhRet, XDisp,c*{c2};
rhVS ← VS LRot0, DISP3{RET}[VAModRet],c*{c3};
{return here if no rh fix or after fix}
USrcVALo ← Q,c*{c1}, at[VAbRet,8,VAModRet];
SrcVAExit:[] ← rhWho, XDisp,c*{c2};
USrcBit ← TempB, DISP2{RET}[SrcVAModRet],c*{c3};
{——————————————————————————————————————————————————————
VAMod SUBROUTINE
first cycle = c3 , last cycle = c2
Timing: 2 clicks, + 1 if neg
This subroutine is used to modify a virtual address.
CALLING ARGUMENTS
rhRetcaller
Qvirtual page and word
TempBplincrement for the address
TempBbit
always UPDATES
Qvirtual page and word
TempBbit
RETURNS
TempBplmodifier for rh
——————————————————————————————————————————————————————}
VAMod:TempB ← TempB + TempBpl, NibCarryBr, GOTO[VAmod1],c*{c1};
VAmod1:TempBpl ← TempBpl and ~0F, NegBr, BRANCH[oldWord, nextWord],c*{c2};
oldWord:TempBpl ← TempBpl LRot12, BRANCH[oldWPos, oldWNeg],c*{c3};
nextWord:TempBpl ← TempBpl LRot12, BRANCH[nextWPos, nextWNeg],c*{c3};
oldWPos:Q ← Q + TempBpl, CarryBr, GOTO[bPP],c*{c1};
bPP:[] ← rhRet, XDisp, BRANCH[oldPSeg, newPSeg],c*{c2};
nextWPos:Q ← Q + TempBpl + 1, CarryBr, GOTO[bPP],c*{c1};
oldWNeg:TempBpl ← TempBpl LRot4,c*{c1};
TempBpl ← TempBpl or 0F,c*{c2};
TempBpl ← TempBpl LRot12,c*{c3};
Q ← Q + TempBpl, CarryBr,c*{c1};
bPN:[] ← rhRet, XDisp, BRANCH[newNSeg, oldNSeg],c*{c2};
nextWNeg:TempBpl ← TempBpl LRot4,c*{c1};
TempBpl ← TempBpl or 0F,c*{c2};
TempBpl ← TempBpl LRot12,c*{c3};
Q ← Q + TempBpl + 1, CarryBr, GOTO[bPN],c*{c1};
oldPSeg:TempBpl ← 0, DISP3{RET}[VAModRet],c*{c3};
newPSeg:TempBpl ← 1, DISP3{RET}[VAModRet,1] {signal rh update},c*{c3};
oldNSeg:TempBpl ← 0, DISP3{RET}[VAModRet],c*{c3};
newNSeg:TempBpl ← {-1}TempBpl xor ~TempBpl, DISP3{RET}[VAModRet,1] {signal rh update},c*{c3};
{——————————————————————————————————————————————————————
SrcLRemap SUBROUTINE
first cycle = c1 , last cycle = c3
This subroutine is used to remap the source virtual address.
CALLING ARGUMENTS
rhRetcaller
USrcVALovirtual source page
rhVSvirtual source rh
always UPDATES
SrcAreal source page and word
rhSrcAreal source rh
USES
UQSavesaved value of Q
UVSsavesaved contents of VS
uTsaved contents or rhVS
RETURNS THRU
SrcRemapReturn
——————————————————————————————————————————————————————}
SrcLRemap:UQSave ← Q,c1;
UXsave ← VS,c2;
VS ← USrcVALoSav, dirDisp,c3;
Q ← 0FF + 1, dirDISP[SrcInc],c1;
SLRFor:VS ← VS + Q, CarryBr,c2, at[dir.forward,dirM,SrcInc];
Q ← rhVS + 1, LOOPHOLE[byteTiming], BRANCH[nofixSRhP,fixSRhP],c3;
fixSRhP:rhVS ← Q LRot0,c1;
fixRSh:Noop,c2;
Noop,c3;
nofixSRhP:Map ← USrcVALoSav ← [rhVS, VS], GOTO[mpS1],c1;
SLRBack:VS ← VS - Q, CarryBr,c2, at[dir.backwards,dirM,SrcInc];
Q ← rhVS - 1, LOOPHOLE[byteTiming], BRANCH[fixSRhN,nofixSRhN],c3;
fixSRhN:rhVS ← Q LRot0, GOTO[fixRSh],c1;
nofixSRhN:Map ← USrcVALoSav ← [rhVS, VS], GOTO[mpS1],c1;
mpS1:Q ← SrcA and 0FF,c2;
SrcA ← MD, rhSrcA ← MD, XRefBr,c3;
Noop, BRANCH[fixSMap, nofixSMap],c1;
nofixSMap:SrcA ← SrcA and ~0FF,c2;
SrcA ← SrcA or Q,c3;
mfsR:Q ← UQSave,c1;
[] ← rhRet, XDisp,c2;
VS ← UXsave, RET[SrcRemapReturn],c3;
fixSMap:Noop,c2;
[] ← SrcA LRot0, XwdDisp,c3;
Map ← [rhVS, VS], DISP2[mapSFixes],c1;
mapSFixes:
MDR ← SrcA or 10, GOTO[mfS1],c2, at[0,4,mapSFixes];
MDR ← SrcA or 10, GOTO[mfS1],c2, at[1,4,mapSFixes];
MDR ← SrcA or 10, GOTO[mfS1],c2, at[2,4,mapSFixes];
GOTO[mfS1],c2, at[3,4,mapSFixes];
mfS1:SrcA ← SrcA and ~0FF,c3;
SrcA ← SrcA or Q,c1;
Noop,c2;
GOTO[mfsR],c3;
{——————————————————————————————————————————————————————
DstLRemap SUBROUTINE
first cycle = c1 , last cycle = c3
This subroutine is used to remap the source virtual address.
CALLING ARGUMENTS
rhRetcaller
UDstVALovirtual source page
rhVDvirtual source rh
always UPDATES
DstAreal source page and word
rhDstAreal source rh
USES
UQSavesaved value of Q
UVDsavesaved contents of VD
uTsaved contents or rhVD
RETURNS THRU
DstRemapReturn
——————————————————————————————————————————————————————}
DstLRemap:UQSave ← Q,c1;
UXsave ← VD,c2;
VD ← UDstVALoSav, dirDisp,c3;
Q ← 0FF + 1, dirDISP[DstInc],c1;
DLRFor:VD ← VD + Q, CarryBr,c2, at[dir.forward,dirM,DstInc];
Q ← rhVD + 1, LOOPHOLE[byteTiming], BRANCH[nofixDRhP,fixDRhP],c3;
fixDRhP:rhVD ← Q LRot0,c1;
fixRDh:Noop,c2;
Noop,c3;
nofixDRhP:Map ← UDstVALoSav ← [rhVD, VD], GOTO[mpD1],c1;
DLRBack:VD ← VD - Q, CarryBr,c2, at[dir.backwards,dirM,DstInc];
Q ← rhVD - 1, LOOPHOLE[byteTiming], BRANCH[fixDRhN,nofixDRhN],c3;
fixDRhN:rhVD ← Q LRot0, GOTO[fixRDh],c1;
nofixDRhN:Map ← UDstVALoSav ← [rhVD, VD], GOTO[mpD1],c1;
mpD1:Q ← DstA and 0FF,c2;
DstA ← MD, rhDstA ← MD, XRefBr,c3;
Noop, BRANCH[fixDMap, nofixDMap],c1;
nofixDMap:DstA ← DstA and ~0FF,c2;
DstA ← DstA or Q,c3;
mfdR:Q ← UQSave,c1;
[] ← rhRet, XDisp,c2;
VD ← UXsave, RET[DstRemapReturn],c3;
fixDMap:Noop,c2;
[] ← DstA LRot0, XwdDisp,c3;
Map ← [rhVD, VD], DISP2[mapDFixes],c1;
mapDFixes:
MDR ← DstA or 0B0, GOTO[mfD1],c2, at[0,4,mapDFixes];
MDR ← DstA or 0B0, GOTO[mfD1],c2, at[1,4,mapDFixes];
{page fault cant happen. Checked before entering loop}
{page fault cant happen. Checked before entering loop}
mfD1:DstA ← DstA and ~0FF,c3;
DstA ← DstA or Q,c1;
Noop,c2;
GOTO[mfdR],c3;
{——————————————————————————————————————————————————————
DstMap SUBROUTINE
first cycle = c3 , last cycle = c3
Timing: 2 1/3 clicks, + 1 if fix map flags
This subroutine is used to map the destination virtual address.
CALLING ARGUMENTS
rhRetcaller
UDstVALovirtual destination
rhVDvirtual destination rh
always UPDATES
DstAreal destination page and word
rhDstAreal destination rh
UDstVALoSavvirtual destination
uses as a temp
Qreal destination page and word
RETURNS THRU
DstMapRet
——————————————————————————————————————————————————————}
DstMap:VD ← UDstVALoSav,c3;
DstMapSpec:Map ← [rhVD, VD],c1;
UDstVALoSav ← VD,c2;
DstA ← MD, rhDstA ← MD, XDirtyDisp,c3;
DMapRef:MAR ← Q ← [rhDstA, VD + 0], BRANCH[upDMap, DMapOK, 1],c1;
DMapOK:[] ← rhRet, XDisp,c2;
DstA ← Q, DISP2{RET}[DstMapRet],c3;
upDMap:Noop,c2;
[] ← DstA LRot0, XwdDisp,c3;
Map ← [rhVD, VD], DISP2[upDMapHere],c1;
upDMapHere:
MDR ← DstA or 0B0, GOTO[mapD],c2, at[0,4,upDMapHere];
MDR ← DstA or 0B0, GOTO[mapD],c2, at[1,4,upDMapHere];
Q ← qWriteProtect, GOTO[DFault],c2, at[2,4,upDMapHere];
Q ← qPageFault, GOTO[DFault],c2, at[3,4,upDMapHere];
mapD:Xbus ← 2, XDisp, GOTO[DMapRef],c3;
{——————————————————————————————————————————————————————
SrcMap SUBROUTINE
first cycle = c3 , last cycle = c3
Timing: 2 1/3 clicks, + 1 if fix map flags
This subroutine is used to map the source virtual address.
CALLING ARGUMENTS
rhRetcaller
USrcVALovirtual source
rhVSvirtual source rh
always UPDATES
SrcAreal source page and word
rhSrcAreal source rh
USrcVALoSavvirtual destination
uses as a temp
Qreal destination page and word
RETURNS THRU
SrcMapRet
——————————————————————————————————————————————————————}
SrcMap:VS ← USrcVALoSav,c3;
SrcMapSpec:Map ← [rhVS, VS],c1;
USrcVALoSav ← VS,c2;
SrcA ← MD, rhSrcA ← MD, XRefBr,c3;
SMapRef:MAR ← Q ← [rhSrcA, VS + 0], BRANCH[upSMap, SMapOK],c1;
SMapOK:[] ← rhRet, XDisp,c2;
SrcA ← Q, DISP3{RET}[SrcMapRet],c3;
upSMap:Noop,c2;
[] ← SrcA LRot0, XwdDisp,c3;
Map ← [rhVS, VS], DISP2[upSMapHere],c1;
upSMapHere:MDR ← SrcA or 10, GOTO[mapS],c2, at[0,4,upSMapHere];
MDR ← SrcA or 10, GOTO[mapS],c2, at[1,4,upSMapHere];
MDR ← SrcA or 10, GOTO[mapS],c2, at[2,4,upSMapHere];
Q ← qPageFault, GOTO[SFault],c2, at[3,4,upSMapHere];
mapS:[] ← 0, ZeroBr, GOTO[SMapRef],c3;
{——————————————————————————————————————————————————————
SavebbRegs SUBROUTINE
length = 2 2/3 clicks
This subroutine is used to move the rh registers in U.
Note that the caller MUST save L before calling.
MOVES
TOSSTK
Gto UGsave
rhGUrhGsave
PCto UPCsave
rhPCUrhPCsave
LUrhLsave
rhLUrhLsave
rhMDSUrhMDSsave
EXITS TO SavebbRegsRet
——————————————————————————————————————————————————————}
SavebbRegs:
L ← rhL,c*{c2}, at[0,10,SavebbRegs];
SaveBlockRegs::
PC ← PC - 1,c*{c3};
SaveBlockRegsx:{Radr same as Ublock containing following Uregs}
UPCsave ← PC,c*{c1};
{the following Uregs are at "xB" to allow "← rh"}
UGsave ← G,c*{c2};
UrhLsave ← L, G ← rhG ,c*{c3};
UrhGsave ← G, PC ← rhPC,c*{c1};
UrhPCsave ← PC, TOS ← rhMDS, pRet2,,c*{c2};
UrhMDSsave ← TOS, RET[SavebbRegsRet],,c*{c3};
{END}