MicroDebuggingImpl.mesa
Copyright © 1985 by Xerox Corporation. All rights reserved.
Willie-sue, March 10, 1986 1:19:22 pm PST
DIRECTORY
Atom USING [MakeAtom],
FS,
IO,
Rope USING [ROPE],
ViewerClasses USING [Viewer],
ViewerIO USING [CreateViewerStreams, GetViewerFromStream],
ViewerOps USING [FindViewer, OpenIcon],
VM USING [AddressForPageNumber, SimpleAllocate],
MicroDefs,
MicroGlobalVars,
MicroOps,
MicroUtils;
MicroDebuggingImpl: CEDAR PROGRAM
IMPORTS
Atom, FS, IO, ViewerIO, ViewerOps, VM,
MicroGlobalVars, MicroOps, MicroUtils
= BEGIN
OPEN MicroDefs, MicroUtils;
printBuffer: LONG POINTER TO WORD;
in, out: IO.STREAM;
TSStream: PROC = {
v: ViewerClasses.Viewer;
name: ROPE = "Micro Debugging";
IF out = NIL THEN {
v ← ViewerOps.FindViewer[name];
[in, out] ← ViewerIO.CreateViewerStreams[name, v, NIL, FALSE];
}
ELSE v ← ViewerIO.GetViewerFromStream[out];
IF v#NIL THEN IF v.iconic THEN ViewerOps.OpenIcon[v];
};
Sc: PROC[ptr: INT, lx: INT] = {
aPtr: LONG POINTER TO WORDLOOPHOLE[ptr];
TSStream[];
out.PutF["\n\n*** Show %g chars, starting at %bB\n\t", IO.int[lx], IO.int[ptr]];
FOR i: INT IN [0..lx) DO
ch: CHAR = GetCharAtPointer[aPtr];
out.PutChar[' ];
IF ch > '\177 THEN {
val: WORD;
TRUSTED { val ← aPtr^ };
out.PutF["\\%03b", IO.int[val]]
}
ELSE
IF ch < '\040 THEN
out.PutF["^%g", IO.char[ch+100B]]
ELSE out.PutChar[ch];
TRUSTED { aPtr ← aPtr + 1 };
ENDLOOP;
out.PutChar['\n];
};
Sw: PROC[ptr: INT, lx: INT] = {
aPtr: LONG POINTER TO WORDLOOPHOLE[ptr];
val: WORD;
TSStream[];
out.PutF["\n\n*** Show %g words, starting at %bB\n\t", IO.int[lx], IO.int[ptr]];
FOR i: INT IN [0..lx) DO
TRUSTED { val ← aPtr^; aPtr ← aPtr + 1; };
out.PutF[" %bB", IO.card[val]];
ENDLOOP;
out.PutChar['\n];
};
Pmds: PROC[sName: ROPE] = {
sObj: SymbolObj = Gs[sName];
mDef: REF INT;
TSStream[];
IF sObj = NIL THEN {
out.PutF["\n\n*** %g is not a symbol\n", IO.rope[sName]];
RETURN
};
IF sObj.sType # macroType THEN {
out.PutF["\n\n*** %g is not a macro\n", IO.rope[sName]];
RETURN
};
mDef ← NARROW[sObj.sData];
ParseMacroDefn[MicroOps.MacroDefnFromIndex[mDef^], sName];
};
Pmd: PROC[offset: NAT] = {
dPtr: LONG POINTER TO WORD ← MicroOps.MacroDefnFromIndex[offset];
ParseMacroDefn[dPtr, NIL];
};
Pa: PROC[ptr: INT] = {
aPtr: LONG POINTER TO WORD;
len: INTEGER;
TSStream[];
TRUSTED {
aPtr ← LOOPHOLE[ptr];
len ← aPtr^-1;
aPtr ← aPtr + 1;
};
out.PutF["\n\n*** Printing an argument of %g chars, starting at %g\n",
IO.int[len], IO.int[ptr]];
IF len = 2 THEN {
ch: CHAR;
TRUSTED { ch ← GetCharAtPointer[aPtr+1] };
SELECT ch FROM
symc => { PrintSymc[aPtr]; RETURN };
numc => { PrintNumc[aPtr]; RETURN };
num6c => { PrintNum6c[aPtr]; RETURN };
ENDCASE => NULL;
};
FOR i: INTEGER IN [0..len) DO
out.PutChar[GetCharAtPointer[aPtr]];
TRUSTED { aPtr ← aPtr + 1 };
ENDLOOP;
};
Sym: PROC[symIndex: INTEGER] RETURNS[SymbolObj] =
{ RETURN[MicroOps.GetSymbol[symIndex] ] };
Gt: PROC[sName: ROPE] = {
sObj: SymbolObj = Gs[sName];
typ: SymbolType;
TSStream[];
IF sObj = NIL THEN {
out.PutF["\n\n*** %g is not a symbol\n", IO.rope[sName]];
RETURN
};
typ ← sObj.sType;
IF typ = addressType THEN {
memSym: INTEGER = sObj.sMisc;
mObj: SymbolObj = MicroOps.GetSymbol[memSym];
out.PutF["\n\n %g is an address in Memory %g", IO.rope[sName], IO.rope[mObj.name]];
}
ELSE out.PutF["\n\n %g is of type: %g\n",
IO.rope[sName], IO.rope[MicroUtils.TypeName[typ]]];
};
St: PROC = {
start: NAT = MicroGlobalVars.stmtTailBottom;
end: NAT = 511;
num: NAT = end - start + 1;
TSStream[];
IF num = 0 THEN {
out.PutRope["\n\n **** the tail of the stmtBuffer is empty\n"];
RETURN
};
out.PutF["\n\n*** Printing %g chars [%g, 512) in tail of the stmt buffer\n",
IO.int[num], IO.int[start] ];
PrintStmtBuffer[start, end];
};
Sb: PROC[start, num: NAT] = {
end: NAT = start+num-1;
TSStream[];
IF num = 0 THEN {
out.PutRope["\n\n **** Num to print is zero\n"];
RETURN
};
out.PutF["\n\n*** Printing %g chars [%g, %g) in the stmt buffer\n",
IO.int[num], IO.int[start], IO.int[end] ];
PrintStmtBuffer[start, end];
};
Ps: PROC = {
print stmt buffer's current contents
end: NAT = MicroGlobalVars.stmtBufferTop - 1;
TSStream[];
IF end = 0 THEN {
out.PutRope["\n\n **** Stmt buffer is empty\n"];
RETURN
};
out.PutF["\n\n*** Printing the first %g chars in the stmt buffer\n", IO.int[end]];
PrintStmtBuffer[1, end];
};
Pst: PROC = { Ps[]; St[]; };
PrintStmtBuffer: PROC[start, end: NAT] = TRUSTED {
current: NAT ← end;
GetPsChar: PROC[which: NAT] RETURNS[CHAR] = TRUSTED INLINE
{ RETURN[MicroUtils.GetCharAtPointer[printBuffer+which]] };
WHILE current >= start DO
ch: CHAR = MicroOps.GetStmtChar[current];
SELECT ch FROM
symc, numc, num6c => {  -- switch order
(printBuffer+current)^ ← MicroOps.GetStmtValue[current-1];
(printBuffer+current-1)^ ← MicroOps.GetStmtValue[current];
current ← current - 1;
};
ENDCASE => (printBuffer+current)^ ← MicroOps.GetStmtValue[current];
current ← current - 1;
ENDLOOP;
current ← start;
WHILE current <= end DO
ch: CHAR = GetPsChar[current];
SELECT ch FROM
symc => {
TRUSTED { PrintSymc[printBuffer+current+1] };
current ← current + 1;
};
numc => {
TRUSTED { PrintNumc[printBuffer+current+1] };
current ← current + 1;
};
num6c => {
TRUSTED { PrintNum6c[printBuffer+current+1] };
current ← current + 1;
};
ENDCASE => out.PutChar[ch];
current ← current + 1;
ENDLOOP;
out.PutChar['\n];
};
ParseMacroDefn: PROC[dPtr: LONG POINTER TO WORD, name: ROPE] = {
len: INTEGER;
TSStream[];
TRUSTED { len ← dPtr^ };
IF len = 0 THEN {
out.PutRope["\n\n ***** Zero length macro - ERROR *****\n"];
RETURN
};
IF name # NIL THEN
out.PutF["\n\n*** Parse macro defn for %g (%g words) starting at %bB\n",
IO.rope[name], IO.int[len], IO.card[LOOPHOLE[dPtr]]]
ELSE out.PutF["\n\n*** Parse macro defn (%g words) starting at %bB\n",
  IO.int[len], IO.card[LOOPHOLE[dPtr]]];
DO
ch: CHAR;
TRUSTED { dPtr ← dPtr + 1};
SELECT ch ← MicroUtils.GetCharAtPointer[dPtr] FROM
Aargn => {
param: INTEGER;
TRUSTED { param ← ( dPtr ← dPtr + 1)^ };
out.PutF[" {Copy %gth arg} ", IO.int[param]];
};
Aarg1 => out.PutRope[" {Copy 1st arg} "];
Aarg2 => out.PutRope[" {Copy 2nd arg} "];
Anargs => out.PutRope[" {Give number of args} "];
symc => {
TRUSTED { dPtr ← dPtr + 1};
PrintSymc[dPtr];
};
numc => {
TRUSTED { dPtr ← dPtr + 1};
PrintNumc[dPtr];
};
num6c => {
TRUSTED { dPtr ← dPtr + 1};
PrintNum6c[dPtr];
};
40C => out.PutRope[" {40C - shouldn't happen}"];
Aend => {
out.PutRope[" {End of macro defn}\n"];
EXIT;
};
ENDCASE => out.PutChar[MicroUtils.GetCharAtPointer[dPtr]];
ENDLOOP;
};
Gs: PROC[name: ROPE] RETURNS[sObj: MicroDefs.SymbolObj] = {
symb: ATOM ← Atom.MakeAtom[name];
symIndex: INTEGER = MicroUtils.LookupAtom[symb];
IF symIndex = 0 THEN RETURN[NIL];
RETURN[MicroOps.GetSymbol[symIndex]];
};
GetValueAtPointer: PROC[ptr: LONG POINTER TO WORD] RETURNS[WORD] =
TRUSTED { RETURN[ptr^] };
GetIntegerAtPointer: PROC[ptr: LONG POINTER TO WORD] RETURNS[INTEGER] =
TRUSTED { RETURN[LOOPHOLE[ptr^, INTEGER]] };
GetNameAtPointer: PROC[ptr: LONG POINTER TO WORD] RETURNS[ROPE] = {
symIndex: INTEGER = GetIntegerAtPointer[ptr];
RETURN[MicroOps.GetSymbol[symIndex].name];
};
GetStmtInteger: PROC[offset: NAT] RETURNS[INTEGER] = TRUSTED
{ RETURN[GetIntegerAtPointer[MicroGlobalVars.stmtBuffer+offset]] };
PrintSymc: PROC[aPtr: LONG POINTER TO WORD] =
{ out.PutF[" {symc: %g} ", IO.rope[GetNameAtPointer[aPtr]] ] };
PrintNumc: PROC[aPtr: LONG POINTER TO WORD] =
{ out.PutF[" {numc: %g} ", IO.int[GetIntegerAtPointer[aPtr]] ] };
PrintNum6c: PROC[aPtr: LONG POINTER TO WORD] =
{ out.PutF[" {symc: %bB} ", IO.card[GetValueAtPointer[aPtr]] ] };
ShowFixupsFile: PROC[name: ROPE] = {
OPEN MicroOps;
fx: STREAM;
TSStream[];
out.PutF["\n\n*** Reading fixups file %g at %g\n", IO.rope[name], IO.time[]];
fx ← FS.StreamOpen[name ! FS.Error => {
out.PutRope[error.explanation];
out.PutChar['\n];
CONTINUE} ];
IF fx = NIL THEN RETURN;
DO
IF fx.EndOf[] THEN EXIT;
out.PutF["memIndex: %g, loc: %g, fePtr: %g, symIndex: %g,",
IO.int[GetWord[fx]], IO.int[GetWord[fx]], IO.int[GetWord[fx]], IO.int[GetWord[fx]]];
out.PutF["\n\tlabelSymIndex: %g, lineCount: %g\n",
IO.int[GetWord[fx]], IO.int[GetWord[fx]]];
ENDLOOP;
fx.Close[];
};
CompareBinaryFiles: PROC[name1, name2: ROPE] = {
OPEN MicroOps;
fx1, fx2: STREAM;
TSStream[];
out.PutF["\n\n*** Comparing the binary files %g & %g at %g\n",
IO.rope[name1], IO.rope[name2], IO.time[]];
fx1 ← FS.StreamOpen[name1 ! FS.Error => {
out.PutRope[error.explanation];
out.PutChar['\n];
CONTINUE} ];
IF fx1 = NIL THEN RETURN;
fx2 ← FS.StreamOpen[name2 ! FS.Error => {
out.PutRope[error.explanation];
out.PutChar['\n];
CONTINUE} ];
IF fx2 = NIL THEN { fx1.Close[]; RETURN };
fx1.SetIndex[0]; fx2.SetIndex[0];
DO
b1, b2: INTEGER;
IF fx1.EndOf[] OR fx2.EndOf[] THEN {
IF fx1.EndOf[] AND fx2.EndOf[] THEN
out.PutRope["\n\t\t*** the files are identical\n"]
ELSE out.PutF["\n\t\t*** the files agree up to pos %g\n", IO.int[fx1.GetIndex[]] ];
EXIT;
};
b1 ← GetInteger[fx1]; b2 ← GetInteger[fx2];
IF b1 = b2 THEN LOOP;
out.PutF["*** files differ at pos %g: %g vs %g - quitting\n",
IO.int[fx1.GetIndex[]-2], IO.int[b1], IO.int[b2]];
EXIT
ENDLOOP;
fx1.Close[]; fx2.Close[];
};
memWidths: ARRAY [0..30) OF INTEGERALL[0];
ShowBinaryFile: PROC[name: ROPE, limit: INTEGER ← 20] = {
OPEN MicroOps;
fx: STREAM;
firstFixup, firstSymbol: BOOLTRUE;
memNum, count: INTEGER ← 0;
TSStream[];
out.PutF["\n\n*** Reading binary file %g at %g\n", IO.rope[name], IO.time[]];
fx ← FS.StreamOpen[name ! FS.Error => {
out.PutRope[error.explanation];
out.PutChar['\n];
CONTINUE} ];
IF fx = NIL THEN RETURN;
out.PutF["\t\tFile is %g bytes long\n\n", IO.int[fx.GetLength[]] ];
fx.SetIndex[0];
DO
bltkType: INTEGER;
IF fx.EndOf[] THEN EXIT;
bltkType ← GetInteger[fx];
IF (count ← count + 1) = limit THEN {
ch: CHAR;
out.PutRope["~~~ Continue? "];
IF (ch ← in.GetChar[]) = '\n OR ch = 'Y OR ch = 'y THEN
{ out.PutChar['\n]; count ← 0 }
ELSE { fx.Close[]; RETURN };
};
SELECT bltkType FROM
MBend =>
{ out.PutRope["*** MBend\n"]; EXIT };
MBdata => {
memWidth: INTEGER = memWidths[memNum];
out.PutF["*** MBdata. lineNum: %g\n\taccWord: ", IO.int[GetInteger[fx]]];
FOR i: INTEGER IN [0.. memWidth) DO
out.PutF[" %b", IO.int[GetWord[fx]] ];
ENDLOOP;
out.PutChar['\n];
};
MBseta =>
out.PutF["*** MBseta. memNum: %g, loc: %g\n",
IO.int[memNum ← GetInteger[fx]], IO.int[GetInteger[fx]] ];
MBfixup => {
IF firstFixup THEN {
out.PutF["*** First Fixup at pos %g\n", IO.int[fx.GetIndex[]-2]];
firstFixup ← FALSE;
};
out.PutF["*** MBfixup. memNum: %g, loc: %g, bits: %g, val: %g\n",
IO.int[GetInteger[fx]], IO.int[GetInteger[fx]],
IO.int[GetInteger[fx]], IO.int[GetInteger[fx]] ];
};
MBmemdef => {
memNum: INTEGER = GetInteger[fx];
widthInBits: INTEGER = GetInteger[fx];
memWidths[memNum] ← (widthInBits+15)/16;
out.PutF["*** MBmemdef. memNum: %g, width (bits): %g, name: ",
IO.int[memNum], IO.int[widthInBits] ];
ReadSymName[fx];
out.PutChar['\n];
};
MBsymbol => {
IF firstSymbol THEN {
out.PutF["*** First Symbol at pos %g\n", IO.int[fx.GetIndex[]-2]];
firstSymbol ← FALSE;
};
out.PutF["*** MBsymbol. memNum: %g, val: %g {",
IO.int[GetInteger[fx]], IO.int[GetInteger[fx]] ];
ReadSymName[fx];
out.PutRope["}\n"];
};
MBext => {
out.PutF["*** MBext. memNum: %g, loc: %g, bits: %g, {",
IO.int[GetInteger[fx]], IO.int[GetInteger[fx]], IO.int[GetInteger[fx]] ];
ReadSymName[fx];
out.PutRope["}\n"];
};
ENDCASE => NULL;
ENDLOOP;
fx.Close[];
};
ReadSymName: PROC[fx: STREAM] = {
DO
ch: CHAR = fx.GetChar[];
IF ch = '\000 THEN EXIT;
out.PutChar[ch];
ENDLOOP;
IF fx.GetIndex[] MOD 2 = 1 THEN [] ← fx.GetChar[];
};
Acw: PROC[size: NAT] RETURNS[acWord: WordSeq] = {
acWord ← NEW[WordSeqRec[size]];
FOR i: NAT IN [0..acWord.length) DO acWord[i] ← 0; ENDLOOP;
};
Gf: PROC[field: ROPE, acWord: WordSeq] RETURNS[val: WORD] = {
sObj: SymbolObj = Gs[field];
IF sObj = NIL THEN {
out.PutF["\n %g is not a name\n", IO.rope[field]];
RETURN[0]
};
IF sObj.sType # fieldType THEN {
out.PutF["\n %g is not a field\n", IO.rope[field]];
RETURN[0]
};
val ← MicroOps.GetBits[acWord, sObj.sMisc, LOOPHOLE[sObj.sVal, INTEGER]];
};
Set6: PROC[acWord: WordSeq, v0, v1, v2, v3, v4, v5: WORD] = {
acWord[0] ← v0;
acWord[1] ← v1;
acWord[2] ← v2;
acWord[3] ← v3;
acWord[4] ← v4;
acWord[5] ← v5;
};
start code
BEGIN
buf: LONG POINTERVM.AddressForPageNumber[VM.SimpleAllocate[2].page];
printBuffer ← LOOPHOLE[buf, LONG POINTER TO WORD];
END;
END.