TestMapCache.mesa
Copyright © 1986 by Xerox Corporation. All rights reserved.
Muchos gratias to Jim Gasbarro
Louis Monier December 28, 1987 3:55:18 pm PST
DIRECTORY
Atom, Basics, BitOps, CD, CDCommandOps, CDOps, CDProperties, CDSequencer, CDIO, Core, CoreCDUser, CDViewer, DynaBusInterface, IO, Logic, Ports, Rope, Rosemary, RosemaryUser, MapCacheChecker, Sisyph, TerminalIO;
TestMapCache: CEDAR PROGRAM
IMPORTS Atom, Basics, BitOps, CDCommandOps, CDIO, CDOps, CDProperties, CoreCDUser, CDViewer, DynaBusInterface, IO, Logic, Ports, Rosemary, RosemaryUser, MapCacheChecker, Sisyph, TerminalIO
~ BEGIN
nSStopIn, DReqTP, DGrantTP, HeaderCycleIn, DataIn, Clock, DBus, Vdd, Gnd: NAT;
dSerialOut: NAT ← 0;
dSerialIn: NAT ← 1;
nDReset: NAT ← 2;
nDFreeze: NAT ← 3;
dExecute: NAT ← 4;
dAddress: NAT ← 5;
dShiftCK: NAT ← 6;
ROPE: TYPE = Core.ROPE;
Port: TYPE = Ports.Port;
Quad: TYPE = DynaBusInterface.Quad;
Cmd: TYPE = DynaBusInterface.Cmd;
DeviceID: TYPE = DynaBusInterface.DeviceID;
Address: TYPE = DynaBusInterface.Address;
qZero: Quad = BitOps.BitQWordZero;
REProc: TYPE = RosemaryUser.TestEvalProc;
--PROC [memory: BOOL ← TRUE, clockEval: BOOL ← FALSE]--
TProc: TYPE = PROC [h: Handle, Eval: REProc];
dBusPrefix: NAT = 20h;
dBusPrefixBits: NAT = 13;
dBusRegAddBits: NAT = 3;
dBusWidth: NAT = 7;
dBusRegAdd: TYPE = [0..8);
devId: [0..1024) = 0;  -- the one for this chip!
devId4: NAT = devId MOD 16;
arbiterTimeout: CARDINAL ← 200;
cmdCount: INT ← 0;
seed: INT ← 1234;
ramdomOps: INT ← 100;
design: CD.Design ← NIL;
Handle: TYPE = REF HandleRec;
HandleRec: TYPE = RECORD[
testPort: Ports.Port ← NIL,
port: Port ← NIL
];
modeFaultCode: NAT=1; -- if IOWrite in user mode
mapFaultCode: NAT=2; -- if Map Cache miss from a MapRqst
readFaultCode: NAT=7; -- if Map Cache miss from an IORead
-- The commands accessible from the user
ReadReg: PROC [h: Handle, Eval: REProc, reg: MapCacheChecker.Reg] ~ {
p: Port ← h.port;
data: CARD ← MapCacheChecker.ReadReg[reg];
add: CARD ← MakeIOAddr[2, ORD[reg]];
Print["IORead: read reg", IO.PutFR[" %g, val=%g ", IO.int[ORD[reg]], IO.int[data]]];
AcquireBus[h, Eval];
p[DataIn].q ← MakeHeader[cmd: IORRqst, add: add];
p[HeaderCycleIn].b ← TRUE;
Cycle[h, Eval, 1];
p[DataIn].q ← qZero; -- data is irrelevant
p[HeaderCycleIn].b ← FALSE;
FinalCycle[h, Eval];
MapCacheChecker.ExpectReply[MakeHeader[cmd: IORRply, add: add], QBottom[data]];
};
ReadEntry: PROC [h: Handle, Eval: REProc, vp: CARD] ~ {
p: Port ← h.port;
add: CARD ← MakeIOAddr[0, vp];
ignored, error: BOOL;
rp: CARD;
flags: [0..16);
data: CARD ← 0;
[ignored, error, rp, flags] ← MapCacheChecker.ReadEntry[vp];
IF ignored THEN RETURN;
data ← BitOps.ILID[rp, data, 0, 22]; -- rp, 22 bits
data ← BitOps.ICID[flags, data, 28, 4]; -- flags
AcquireBus[h, Eval];
p[DataIn].q ← MakeHeader[cmd: IORRqst, add: add];
p[HeaderCycleIn].b ← TRUE;
Cycle[h, Eval, 1];
p[DataIn].q ← qZero; -- data is irrelevant
p[HeaderCycleIn].b ← FALSE;
FinalCycle[h, Eval];
IF error THEN {
errWord: CARD ← BitOps.ICID[devId, 0, 0, 10]; -- device ID
errWord ← BitOps.ICID[readFaultCode, errWord, 29, 3]; -- error code
Print["IORead entry (error)"];
MapCacheChecker.ExpectReply[MakeHeader[cmd: IORRply, error: TRUE, add: add], QBottom[errWord]];
}
ELSE {
Print["IORead entry"];
MapCacheChecker.ExpectReply[MakeHeader[cmd: IORRply, add: add], QBottom[data]];
};
};
IORead: PROC [h: Handle, Eval: REProc, opCode: [0..4), vp: CARD, data: CARD] ~ {
p: Port ← h.port;
add: CARD ← MakeIOAddr[opCode, vp];
AcquireBus[h, Eval];
p[DataIn].q ← MakeHeader[cmd: IORRqst, add: add];
p[HeaderCycleIn].b ← TRUE;
Cycle[h, Eval, 1];
p[DataIn].q ← qZero; -- data is irrelevant
p[HeaderCycleIn].b ← FALSE;
FinalCycle[h, Eval];
MapCacheChecker.ExpectReply[MakeHeader[cmd: IORRply, add: add], QBottom[data]];
};
WriteReg: PROC [h: Handle, Eval: REProc, reg: MapCacheChecker.Reg, data: CARD, broadcast: BOOLFALSE] ~ {
add: CARD;
MapCacheChecker.WriteReg[reg, data];
add ← IOWrite[h, Eval, 2, ORD[reg], data, broadcast];
IF ~broadcast THEN MapCacheChecker.ExpectReply[MakeHeader[cmd: IOWRply, add: add], qZero, TRUE];
};
-- valid=0 => flush, valid=1 => write
WriteEntry: PROC [h: Handle, Eval: REProc, valid: BOOL, vp, rp: CARD, f: [0..16), broadcast: BOOLFALSE] ~ {
ignored: BOOL;
data, add: CARD ← 0;
data ← BitOps.ILID[rp, data, 0, 22]; -- rp, 22 bits
data ← BitOps.ICID[f, data, 28, 4]; -- flags
ignored ← MapCacheChecker.WriteEntry[valid, vp, rp, f];
IF ignored THEN RETURN; -- vp out of range
add ← IOWrite[h, Eval, IF valid THEN 1 ELSE 0, vp, data, broadcast];
IF ~broadcast THEN MapCacheChecker.ExpectReply[MakeHeader[cmd: IOWRply, add: add], qZero, TRUE];
};
IOWrite: PROC [h: Handle, Eval: REProc, opCode: [0..4), vp: CARD, data: CARD, broadcast: BOOLFALSE] RETURNS [add: CARD] ~ {
p: Port ← h.port;
add ← MakeIOAddr[opCode, vp];
AcquireBus[h, Eval];
IF broadcast THEN {
Print["BIOWrite"];
p[DataIn].q ← MakeHeader[cmd: BIOWRqst, add: add];
}
ELSE {
Print["IOWrite"];
p[DataIn].q ← MakeHeader[cmd: IOWRqst, add: add];
};
p[HeaderCycleIn].b ← TRUE;
Cycle[h, Eval, 1];
p[DataIn].q ← QBottom[data];
p[HeaderCycleIn].b ← FALSE;
FinalCycle[h, Eval];
};
MapRqst: PROC [h: Handle, Eval: REProc, vp, aid: CARD] ~ {
p: Port ← h.port;
vp32: CARD ← 0;
ignored, error: BOOL;
rp: CARD;
flags: [0..16);
[ignored, error, rp, flags] ← MapCacheChecker.Map[vp, aid];
IF ignored THEN RETURN;
vp32 ← BitOps.ILID[vp, vp32, 0, 22]; -- vp in high-order bits
AcquireBus[h, Eval];
p[DataIn].q ← MakeHeader[cmd: MapRqst, add: vp32];
p[HeaderCycleIn].b ← TRUE;
Cycle[h, Eval, 1];
p[DataIn].q ← QBottom[aid];
p[HeaderCycleIn].b ← FALSE;
FinalCycle[h, Eval];
IF error THEN {
errWord: CARD ← BitOps.ICID[devId, 0, 0, 10]; -- device ID
errWord ← BitOps.ICID[mapFaultCode, errWord, 29, 3]; -- error code
Print["MapRqst (error)"];
MapCacheChecker.ExpectReply[MakeHeader[cmd: MapRply, error: TRUE, add: vp32], QBottom[errWord]];
}
ELSE {
rpf: CARD ← BitOps.ILID[rp, 0, 0, 22]; -- rp, 22 bits
rpf ← BitOps.ICID[flags, rpf, 28, 4]; -- flags
Print["MapRqst"];
MapCacheChecker.ExpectReply[MakeHeader[cmd: MapRply, add: rpf], qZero, TRUE];
};
};
SimpleTest: RosemaryUser.TestProc = {
h: Handle ← NEW[HandleRec];
m1: CARD=0FFFFH;
FindDesign[];
h.port ← p;
InitPortIndicies[cellType];
cmdCount ← 0;
Reset[h, Eval];
ReadID[h, Eval]; -- check this
-- set registers to a reasonnable value
WriteReg[h, Eval, aidR, 13H];
WriteReg[h, Eval, shP, 100000H];
WriteReg[h, Eval, shM, 100000H];
WriteReg[h, Eval, byP, 200000H];
WriteReg[h, Eval, byM, 200000H];
WriteReg[h, Eval, byB, 0H];
WriteReg[h, Eval, vpP, 0H];
WriteReg[h, Eval, vpM, 0H];
ReadReg[h, Eval, aidR];  -- IORead: aid
-- Test Physical region (aid=-1)
MapRqst[h, Eval, 136H, m1]; -- aid=-1 => rp=vp
WriteReg[h, Eval, aidR, m1];
ReadEntry[h, Eval, 136H];
WriteReg[h, Eval, aidR, 13H];
-- Test Bypass Area
MapRqst[h, Eval, 200123H, 4H]; -- vp in Bypass => compute rp
ReadEntry[h, Eval, 200123H];
-- Test Shared Area
WriteReg[h, Eval, aidR, 0];  -- aid=0
WriteEntry[h, Eval, TRUE, 100067H, 742H, 5H]; -- set rp for vp in Shared
WriteReg[h, Eval, aidR, 13H]; -- restore aid
MapRqst[h, Eval, 100067H, 3]; -- vp in Shared => use aid=0
ReadEntry[h, Eval, 100067H];
-- Normal case
WriteEntry[h, Eval, TRUE, 135H, 742H, 5H]; -- IOWrite: entry 135
WriteEntry[h, Eval, TRUE, 136H, 744H, 3H];  -- IOWrite: entry 136 
ReadEntry[h, Eval,   135H];   -- IORead: entry 135
ReadEntry[h, Eval,   136H];   -- IORead: entry 136
MapRqst[h, Eval, 135H, 13H];
-- Flush one entry
WriteEntry[h, Eval, FALSE, 135H, 0, 0]; -- IOWrite: flush entry 135
-- Access valid entry
MapRqst[h, Eval, 136H, 13H];
-- Access invalid entry: should fail!
MapRqst[h, Eval, 135H, 13H];
ReadEntry[h, Eval, 135H];
-- Test Subset of vp: even addresses are ignored
WriteReg[h, Eval, vpP, 0H];
WriteReg[h, Eval, vpM, 1H];
WriteEntry[h, Eval, TRUE, 130H, 0, 0]; -- ignored
WriteEntry[h, Eval, TRUE, 131H, 0, 0]; -- done
WriteReg[h, Eval, vpP, 0H];
WriteReg[h, Eval, vpM, 0H];
FlushPipe[h, Eval];
};
-- try to exercice all nodes
SimpleTest: RosemaryUser.TestProc = {
h: Handle ← NEW[HandleRec];
FindDesign[];
h.port ← p;
InitPortIndicies[cellType];
cmdCount ← 0;
Reset[h, Eval];
ReadID[h, Eval]; -- check this
-- wiggle all registers
FOR i: NAT IN [0..8) DO
reg: MapCacheChecker.Reg ← VAL[i];
WriteReg[h, Eval, reg, 0];
ReadReg[h, Eval, reg];
WriteReg[h, Eval, reg, 03FFFFFH];
ReadReg[h, Eval, reg];
ENDLOOP;
WriteReg[h, Eval, aidR, 13H];
WriteReg[h, Eval, shP, 100000H];
WriteReg[h, Eval, shM, 100000H];
WriteReg[h, Eval, byP, 200000H];
WriteReg[h, Eval, byM, 200000H];
WriteReg[h, Eval, byB, 0H];
WriteReg[h, Eval, vpP, 0H];
WriteReg[h, Eval, vpM, 0H];
-- access all of the ram
FOR i: NAT IN [0..256) DO
WriteEntry[h, Eval, TRUE, i, 0, 0];
MapRqst[h, Eval, i, 13H];
ENDLOOP;
FlushPipe[h, Eval];
};
ReadID: TProc ~ {
ENABLE Rosemary.Stop => IF reason = $BoolWireHasX THEN RESUME;
DBusRegRead[h, Eval, 0, [0, 0, 0, 5240h], 16]; --header=5, type=9, version=0
};
Reset: TProc ~ {
ENABLE Rosemary.Stop => IF reason = $BoolWireHasX THEN RESUME;
p: Port ← h.port;
TerminalIO.PutRope["***Reset***\n"];
p[DBus].bs[nDReset] ← FALSE;
p[nSStopIn].b ← TRUE;
p[DBus].bs[dShiftCK] ← FALSE;
DBusRegWrite[h, Eval, 1, 0, 10];
p[HeaderCycleIn].b ← FALSE;
p[DataIn].q ← qZero;
p[DReqTP].c ← 0; -- no request
Cycle[h, Eval, 7];
p[nSStopIn].b ← FALSE;
Cycle[h, Eval, 5];
p[DBus].bs[nDReset] ← TRUE;
Cycle[h, Eval, 5];
p[nSStopIn].b ← TRUE;
Cycle[h, Eval, 5];
p[DGrantTP].d ← expect;
p[DGrantTP].b ← FALSE;
IOWrite2[h, Eval, 1, 10];
FlushPipe[h, Eval];
};
DBusRegSel: PROC [h: Handle, Eval: REProc, add: dBusRegAdd] ~ {
bits: CARDINAL ← dBusPrefix;
p: Port ← h.port;
p[DBus].bs[dAddress] ← TRUE;
FOR i: NAT IN [0..dBusPrefixBits) DO
p[DBus].bs[dSerialIn] ← Basics.BITAND[bits, Basics.BITSHIFT[1, dBusPrefixBits-1]]#0; --send MSB first
bits ← Basics.BITSHIFT[bits, 1];
DBusCycle[h, Eval];
ENDLOOP;
bits ← add;
FOR i: NAT IN [0..dBusRegAddBits) DO
p[DBus].bs[dSerialIn] ← Basics.BITAND[bits, Basics.BITSHIFT[1, dBusRegAddBits-1]]#0; --send MSB first
bits ← Basics.BITSHIFT[bits, 1];
DBusCycle[h, Eval];
ENDLOOP;
p[DBus].bs[dAddress] ← FALSE;
};
DBusRegRead: PROC [h: Handle, Eval: REProc, add: dBusRegAdd, data: BitOps.BitQWord, regWidth: [1..BitOps.bitsPerQWord]] ~ {
p: Port ← h.port;
DBusRegSel[h, Eval, add];
p[DBus].bs[dExecute] ← TRUE;
p[DBus].ds[dSerialOut] ← expect;
p[DBus].bs[dSerialOut] ← BitOps.EBFQ[data, 0, regWidth];
DBusCycle[h, Eval];
p[DBus].bs[dExecute] ← FALSE;
FOR i: NAT IN [1..regWidth) DO
p[DBus].bs[dSerialOut] ← BitOps.EBFQ[data, i, regWidth];
DBusCycle[h, Eval];
ENDLOOP;
p[DBus].ds[dSerialOut] ← none;
};
DBusRegWrite: PROC [h: Handle, Eval: REProc, add: dBusRegAdd, data: BitOps.BitDWord, regWidth: [1..BitOps.bitsPerDWord]] ~ {
p: Port ← h.port;
DBusRegSel[h, Eval, add];
FOR i: NAT IN [0..regWidth) DO
p[DBus].bs[dSerialIn] ← BitOps.EBFD[data, i, regWidth];
DBusCycle[h, Eval];
ENDLOOP;
};
Cycle: PROC [h: Handle, Eval: REProc, n: CARDINAL ← 1] ~ {
p: Port ← h.port;
THROUGH [0..n) DO
Eval[TRUE, FALSE, FALSE]; --ignore errors before clock rises
p[Clock].b ← TRUE;
Eval[TRUE, TRUE, FALSE]; --ignore errors during clockEval
Eval[TRUE, FALSE, TRUE];
p[Clock].b ← FALSE;
Eval[TRUE, TRUE, TRUE];
ENDLOOP;
};
DBusCycle: TProc ~ {
p: Port ← h.port;
Eval[TRUE, FALSE, FALSE];
p[DBus].bs[dShiftCK] ← TRUE;
Eval[TRUE, TRUE, FALSE];
Eval[TRUE, FALSE, TRUE];
p[DBus].bs[dShiftCK] ← FALSE;
Eval[TRUE, TRUE, TRUE];
};
FlushPipe: TProc ~ {
WHILE ~MapCacheChecker.IsEmpty[] DO
Cycle[h, Eval, 1];
ENDLOOP;
};
AcquireBus: PROC [h: Handle, Eval: REProc ] ~ {
timer: CARDINAL ← arbiterTimeout;
p: Port ← h.port;
p[DReqTP].c ← 2;
Cycle[h, Eval, 1];
p[DReqTP].c ← 0; -- no further request
p[DGrantTP].d ← inspect; -- p[DGrantTP].b = FALSE
WHILE NOT p[DGrantTP].b DO
Cycle[h, Eval, 1];
timer ← timer-1;
IF timer=0 THEN ERROR; --bus timeout
ENDLOOP;
p[DGrantTP].d ← expect; -- p[DGrantTP].b = TRUE
};
FinalCycle: TProc ~ {
p: Port ← h.port;
p[DGrantTP].b ← FALSE;
Cycle[h, Eval, 1];
};
Print: PROC [cmd, r1, r2, r3: ROPENIL] ~ {
TerminalIO.PutRopes[IO.PutFR["\n%g) ", IO.int[cmdCount]], cmd];
TerminalIO.PutRopes[r1, r2, r3];
cmdCount ← cmdCount+1;
};
MakeHeader: PROC [cmd: Cmd, error: BOOLFALSE, id: DeviceID ← 0, add: CARD ← 0] RETURNS [header: Quad] ~ {
header ← qZero;
header ← DynaBusInterface.InsertCmd[header, cmd];
header ← DynaBusInterface.InsertModeError[header, error];
header ← DynaBusInterface.InsertShared[header, FALSE];
header ← DynaBusInterface.InsertDeviceID[header, id];
header[2] ← Basics.HighHalf[add];
header[3] ← Basics.LowHalf[add];
};
MakeIOAddr: PROC [opCode: [0..4), vp: CARD] RETURNS [add: CARD] ~ {
add ← 0;
add ← BitOps.ICID[5, add, 0, 4]; -- mapcache type=5
add ← BitOps.ICID[devId4, add, 4, 4]; -- low-order four bits of devId
add ← BitOps.ICID[opCode, add, 8, 2];
add ← BitOps.ILID[vp, add, 10, 22];
};
QBottom: PROC [data: CARD] RETURNS [Quad] ~ {
RETURN[[0, 0, Basics.HighHalf[data], Basics.LowHalf[data]]];
};
DoExtract: PROC ~ {
ct: Core.CellType ← NIL;
ct ← Sisyph.ExtractSchematicByName["MapCacheSim.sch", Sisyph.Create[design]];
CDProperties.PutDesignProp[design, $MapCacheCellType, ct];
};
CDExtract: PROC [comm: CDSequencer.Command] = {
design ← comm.design;
DoExtract[];
};
Extract: PROC [fileName: ROPENIL, wDir: ROPENIL] ~ {
FindDesign[fileName, wDir];
DoExtract[];
};
FindDesign: PROC [fileName: ROPENIL, wDir: ROPENIL] ~ {
IF design=NIL THEN design ← NARROW[Atom.GetProp[$MapCache, $Design]];
IF design=NIL THEN design ← CDViewer.FindDesign["MapCache"];
IF design=NIL THEN {
design ← CDIO.ReadDesign[fileName, NIL, wDir];
CDOps.SetMutability[design];
Viewer[];
};
Atom.PutProp[$MapCache, $Design, design];
};
Viewer: PROC ~ {
[] ← CDViewer.CreateViewer[design];
};
StartTest: PROC ~ {
RosemaryUser.StartTest[NARROW[CDProperties.GetDesignProp[design, $MapCacheTester], RosemaryUser.Tester]];
};
InitPortIndicies: PROC [ct: Core.CellType] ~ {
[nSStopIn, DReqTP, DGrantTP, HeaderCycleIn, DataIn, Clock, DBus, Vdd, Gnd] ← Ports.PortIndexes[ct.public, "nSStopIn", "DReqTP", "DGrantTP", "HeaderCycleIn", "DataIn", "Clock", "DBus", "Vdd", "Gnd"];
};
Simulate: PROC = {
tester: RosemaryUser.Tester ← NIL;
ct: Core.CellType ← NIL;
ds: Ports.DriveSequence ← NEW[Ports.DriveSequenceRec[dBusWidth]];
IF design=NIL THEN ERROR;
ct ← NARROW[CDProperties.GetDesignProp[design, $MapCacheCellType]];
FOR i: NAT IN [0..dBusWidth) DO
ds[i] ← IF i=dSerialOut THEN none ELSE force;
ENDLOOP;
InitPortIndicies[ct];
Ports.ITDList[ct.public, LIST[nSStopIn], drive];
Ports.ITDList[ct.public, LIST[DReqTP, HeaderCycleIn, DataIn, Clock], force];
Ports.IPList[ct.public, LIST[DReqTP], c];
Ports.IPList[ct.public, LIST[DataIn], q];
[] ← Ports.InitPort[wire: ct.public[DBus], levelType: bs];
[] ← Ports.InitTesterDrive[wire: ct.public[DBus], initDrives: ds];
[] ← Rosemary.SetFixedWire[ct.public[Vdd], H];
[] ← Rosemary.SetFixedWire[ct.public[Gnd], L];
tester ← RosemaryUser.TestProcedureViewer[cellType: ct, testButtons: LIST["SimpleTest"], name: "MapCache Tester", displayWires: RosemaryUser.DisplayPortLeafWires[ct], cutSet: Logic.fast];
CDProperties.PutDesignProp[design, $MapCacheTester, tester];
CoreCDUser.SetDesignRootCellType[design, ct];
CoreCDUser.SetRootCellTypeDecoration[ct, Sisyph.mode.decoration];
};
RosemaryUser.RegisterTestProc["SimpleTest", SimpleTest];
CDCommandOps.RegisterWithMenu[
menu: $ProgramMenu,
entry: "Extract MC",
doc: "",
proc: CDExtract
];
END.