DIRECTORY Basics USING [bytesPerWord, Word], BasicTime USING [FromNSTime], BcdDefs USING [ BCD, FTIndex, FTNull, FTRecord, FTSelf, Link, NameRecord, MTIndex, MTRecord, SGIndex, SGRecord, VersionStamp], Commander USING [CommandProc, Handle, Register], FS USING [Error], IO USING [EndOfStream, GetTokenRope, IDProc, PutChar, PutF, PutFR, PutRope, RIS, STREAM], Rope USING [ActionType, Cat, Concat, Equal, Fetch, Flatten, Length, Map, Match, Substr, ROPE, Run], RuntimeError USING [UNCAUGHT], SymbolSegment USING [BlockDescriptor, FGHeader, STHeader], RopeFile USING [SimpleCreate], VM USING [wordsPerPage]; BcdCompare: CEDAR PROGRAM IMPORTS BasicTime, Commander, FS, IO, Rope, RuntimeError, RopeFile = BEGIN BCD: TYPE = BcdDefs.BCD; BcdPtr: TYPE = LONG POINTER TO BCD; BlockDescriptor: TYPE = SymbolSegment.BlockDescriptor; Buffer: TYPE = REF BufferRep; BufferRep: TYPE = RECORD [start: INT _ 0, len: NAT _ 0, words: SEQUENCE max: NAT OF Word]; FGHeader: TYPE = SymbolSegment.FGHeader; NameRecord: TYPE = BcdDefs.NameRecord; ROPE: TYPE = Rope.ROPE; Stats: TYPE = REF StatsRep; StatsRep: TYPE = RECORD [ debug, doCode, doSymbols, doAll: BOOL _ FALSE, name1,name2: ROPE _ NIL, rope1,rope2: ROPE _ NIL, base1,base2: LONG POINTER _ NIL, symOff1,symOff2: INT _ 0, leader: ROPE _ NIL, out: STREAM _ NIL, maxTabLim1: INT _ 0, maxTabLim2: INT _ 0, errors: NAT _ 0, maxErrors: NAT _ 0 ]; STREAM: TYPE = IO.STREAM; SymbolTableHeader: TYPE = REF SymbolSegment.STHeader; VersionStamp: TYPE = BcdDefs.VersionStamp; Word: TYPE = Basics.Word; WordPtr: TYPE = LONG POINTER TO Word; bytesPerWord: NAT = Basics.bytesPerWord; wordsPerPage: NAT = VM.wordsPerPage; bytesPerPage: NAT = wordsPerPage*bytesPerWord; GiveUp: ERROR [err: ROPE] = CODE; initMaxErrors: NAT _ 24; blockList: LIST OF ROPE = LIST[ "hvBlock", "htBlock", "ssBlock", "outerPackBlock", "innerPackBlock", "constBlock", "seBlock", "ctxBlock", "mdBlock", "bodyBlock", "extBlock", "treeBlock", "litBlock", "sLitBlock", "epMapBlock", "spareBlock"]; DoCompare: Commander.CommandProc = { in: STREAM = IO.RIS[cmd.commandLine]; name1,name2: ROPE; name1 _ IO.GetTokenRope[in, IO.IDProc ! IO.EndOfStream => GO TO usage].token; name2 _ IO.GetTokenRope[in, IO.IDProc ! IO.EndOfStream => GO TO usage].token; CompareFilesAsBcds[ cmd, name1, name2 ! GiveUp => {msg _ err; GO TO errOut}; FS.Error => {msg _ error.explanation; GO TO errOut}]; msg _ "No differences found."; EXITS errOut => result _ $Failure; usage => {result _ $Failure; msg _ "Usage: CodeCompare file1 file2"}; }; CompareFilesAsBcds: PROC [cmd: Commander.Handle, name1,name2: ROPE] = { rope1: ROPE = RopeFile.SimpleCreate[name1 _ ForceExtension[name1, ".bcd"]]; rope2: ROPE = RopeFile.SimpleCreate[name2 _ ForceExtension[name2, ".bcd"]]; stats: Stats = NEW[StatsRep]; ProcessOptions[stats, cmd.procData.clientData]; IF stats.debug THEN stats.maxErrors _ initMaxErrors*4 ELSE stats.maxErrors _ initMaxErrors; stats.out _ cmd.out; stats.name1 _ name1; stats.name2 _ name2; stats.rope1 _ rope1; stats.rope2 _ rope2; CompareRopesAsBcds[rope1, rope2, stats]; }; ProcessOptions: PROC [stats: Stats, data: REF] = { WITH data SELECT FROM atom: ATOM => SELECT atom FROM $Code => stats.doCode _ TRUE; $All => stats.doAll _ TRUE; $Symbols => stats.doSymbols _ TRUE; $Debug => stats.debug _ stats.doAll _ TRUE; ENDCASE; list: LIST OF REF => WHILE list # NIL DO ProcessOptions[stats, list.first]; list _ list.rest; ENDLOOP; ENDCASE; }; ForceExtension: PROC [name: ROPE, ext: ROPE] RETURNS [ROPE] = { match: ROPE _ Rope.Concat["*", ext]; SELECT TRUE FROM Rope.Match["*!*", name], match.Match[name, FALSE] => {}; ENDCASE => name _ name.Concat[ext]; RETURN [name]; }; CompareRopesAsBcds: PROC [rope1,rope2: ROPE, stats: Stats] = TRUSTED { bcdBuf1: Buffer = NEW[BufferRep[SIZE[BCD]]]; bcd1: BcdPtr = LOOPHOLE[@bcdBuf1[0]]; bcdBuf2: Buffer = NEW[BufferRep[SIZE[BCD]]]; bcd2: BcdPtr = LOOPHOLE[@bcdBuf2[0]]; len: INT = MIN[rope1.Length[], rope2.Length[]]; GetWords[rope1, 0, SIZE[BCD], bcdBuf1]; GetWords[rope2, 0, SIZE[BCD], bcdBuf2]; stats.base1 _ bcd1; stats.base2 _ bcd2; IO.PutRope[stats.out, stats.name1]; IO.PutRope[stats.out, "\n version: "]; VersionOut[bcd1.version, stats, TRUE]; IO.PutF[stats.out, ", bytes: %g\n source: ", [integer[rope1.Length[]]]]; NameOut[rope1, bcd1.ssOffset, bcd1.source, stats]; IO.PutRope[stats.out, "\n sourceVersion: "]; VersionOut[bcd1.sourceVersion, stats]; IO.PutRope[stats.out, "\n"]; IO.PutRope[stats.out, stats.name2]; IO.PutRope[stats.out, "\n version: "]; VersionOut[bcd2.version, stats, TRUE]; IO.PutF[stats.out, ", bytes: %g\n source: ", [integer[rope2.Length[]]]]; NameOut[rope2, bcd2.ssOffset, bcd2.source, stats]; IO.PutRope[stats.out, "\n sourceVersion: "]; VersionOut[bcd2.sourceVersion, stats]; IO.PutRope[stats.out, "\n"]; IF rope1.Length[] # rope2.Length[] THEN { IO.PutRope[stats.out, "Warning, files have different lengths.\n"]; stats.errors _ stats.errors +1; }; CompareEntries[ "In versionIdent\n", @bcd1.versionIdent, @bcd2.versionIdent, SIZE[CARDINAL], stats]; CompareEntries[ "In version\n", @bcd1.version, @bcd2.version, SIZE[VersionStamp], stats]; CompareEntries[ "In creator\n", @bcd1.creator, @bcd2.creator, SIZE[VersionStamp], stats]; CompareEntries[ "In sourceVersion\n", @bcd1.sourceVersion, @bcd2.sourceVersion, SIZE[VersionStamp], stats]; CompareEntries[ "In source\n", @bcd1.source, @bcd2.source, SIZE[NameRecord], stats]; CompareEntries[ "In nPages\n", @bcd1.nConfigs-1, @bcd2.nConfigs-1, SIZE[CARDINAL], stats]; CompareEntries[ "In nConfigs\n", @bcd1.nConfigs, @bcd2.nConfigs, SIZE[CARDINAL], stats]; CompareEntries[ "In nModules\n", @bcd1.nModules, @bcd2.nModules, SIZE[CARDINAL], stats]; CompareEntries[ "In nImports\n", @bcd1.nImports, @bcd2.nImports, SIZE[CARDINAL], stats]; CompareEntries[ "In options (definitions, repackaged, typeExported, tableCompiled, versions, extended)\n", @bcd1.nDummies-1, @bcd2.nDummies-1, SIZE[CARDINAL], stats]; CompareEntries[ "In nDummies\n", @bcd1.nDummies, @bcd2.nDummies, SIZE[CARDINAL], stats]; IF stats.debug THEN IO.PutRope[stats.out, "** Tables\n"]; CompareTables[ "string table", @bcd1.ssOffset, @bcd2.ssOffset, stats]; CompareTables[ "config table", @bcd1.ctOffset, @bcd2.ctOffset, stats]; CompareTables[ "module table", @bcd1.mtOffset, @bcd2.mtOffset, stats]; CompareTables[ "import table", @bcd1.impOffset, @bcd2.impOffset, stats]; CompareTables[ "export table", @bcd1.expOffset, @bcd2.expOffset, stats]; CompareTables[ "external variable table", @bcd1.evOffset, @bcd2.evOffset, stats]; CompareTables[ "segment table", @bcd1.sgOffset, @bcd2.sgOffset, stats]; CompareTables[ "file table", @bcd1.ftOffset, @bcd2.ftOffset, stats]; CompareTables[ "space table", @bcd1.spOffset, @bcd2.spOffset, stats]; CompareTables[ "name table", @bcd1.ntOffset, @bcd2.ntOffset, stats]; CompareTables[ "type table", @bcd1.typOffset, @bcd2.typOffset, stats]; CompareTables[ "type map table", @bcd1.tmOffset, @bcd2.tmOffset, stats]; CompareTables[ "frame pack table", @bcd1.fpOffset, @bcd2.fpOffset, stats]; IF bcd1.extended AND bcd2.extended THEN { CompareTables[ "link fragment table", @bcd1.lfOffset, @bcd2.lfOffset, stats, TRUE]; CompareTables[ "ref literal fragment table", @bcd1.rfOffset, @bcd2.rfOffset, stats, TRUE]; CompareTables[ "type fragment table", @bcd1.tfOffset, @bcd2.tfOffset, stats, TRUE]; CompareEntries[ "In rtPages\n", @bcd1.rtPages, @bcd2.rtPages, SIZE[CARDINAL], stats]; }; IF stats.debug THEN { IO.PutRope[stats.out, "** Segments for file 1\n"]; SegmentsOut[rope1, bcd1, stats]; IO.PutRope[stats.out, "** Segments for file 2\n"]; SegmentsOut[rope2, bcd2, stats]; }; IF stats.debug THEN { IO.PutRope[stats.out, "** Files for file 1\n"]; FilesOut[rope1, bcd1, stats]; IO.PutRope[stats.out, "** Files for file 2\n"]; FilesOut[rope2, bcd2, stats]; }; {-- compare the code in the various modules mti1: CARDINAL _ LOOPHOLE[FIRST[BcdDefs.MTIndex], CARDINAL]+bcd1.mtOffset; mti2: CARDINAL _ LOOPHOLE[FIRST[BcdDefs.MTIndex], CARDINAL]+bcd2.mtOffset; FOR i: NAT IN [0..MIN[bcd1.nModules,bcd2.nModules]) DO mtr1: BcdDefs.MTRecord; mtr2: BcdDefs.MTRecord; sgr1: BcdDefs.SGRecord; sgr2: BcdDefs.SGRecord; nw1,nw2,sgi1,sgi2: CARDINAL; byteOff1,byteOff2: INT; sb1,sb2: INT; GetWordsToPtr[rope1, mti1, SIZE[BcdDefs.MTRecord], @mtr1]; GetWordsToPtr[rope2, mti2, SIZE[BcdDefs.MTRecord], @mtr2]; WITH m: mtr1 SELECT FROM direct => nw1 _ SIZE[BcdDefs.MTRecord[direct]] + m.length*SIZE[BcdDefs.Link]; indirect => nw1 _ SIZE[BcdDefs.MTRecord[indirect]]; multiple => nw1 _ SIZE[BcdDefs.MTRecord[multiple]]; ENDCASE => ERROR; WITH m: mtr2 SELECT FROM direct => nw2 _ SIZE[BcdDefs.MTRecord[direct]] + m.length*SIZE[BcdDefs.Link]; indirect => nw2 _ SIZE[BcdDefs.MTRecord[indirect]]; multiple => nw2 _ SIZE[BcdDefs.MTRecord[multiple]]; ENDCASE => ERROR; IF stats.doCode OR stats.doAll THEN { sgi1 _ bcd1.sgOffset + LOOPHOLE[mtr1.code.sgi, CARDINAL]; sgi2 _ bcd2.sgOffset + LOOPHOLE[mtr2.code.sgi, CARDINAL]; GetWordsToPtr[rope1, sgi1, SIZE[BcdDefs.SGRecord], @sgr1]; GetWordsToPtr[rope2, sgi2, SIZE[BcdDefs.SGRecord], @sgr2]; sb1 _ (sgr1.base-1)*INT[wordsPerPage]; sb2 _ (sgr2.base-1)*INT[wordsPerPage]; byteOff1 _ (mtr1.code.offset+sb1)*bytesPerWord; byteOff2 _ (mtr2.code.offset+sb2)*bytesPerWord; SELECT TRUE FROM mtr1.code.length = 0 AND mtr2.code.length = 0 => IO.PutRope[stats.out, "No code.\n"]; mtr1.code.length = 0 => IO.PutF[ stats.out, "No code for file 1, %g bytes for file 2.\n", [integer[mtr2.code.length]]]; mtr1.code.length = 0 => IO.PutF[ stats.out, "No code for file 2, %g bytes for file 1.\n", [integer[mtr1.code.length]]]; ENDCASE => CompareBytes[ IO.PutFR[ "In code for %g (module %g)\n", [rope[GetName[rope1, bcd1.ssOffset, mtr1.name]]], [integer[i]]], byteOff1, byteOff2, MIN[mtr1.code.length, mtr2.code.length], stats]; }; IF stats.doSymbols OR stats.doAll THEN { sgi1 _ bcd1.sgOffset + LOOPHOLE[mtr1.sseg, CARDINAL]; sgi2 _ bcd2.sgOffset + LOOPHOLE[mtr2.sseg, CARDINAL]; GetWordsToPtr[rope1, sgi1, SIZE[BcdDefs.SGRecord], @sgr1]; GetWordsToPtr[rope2, sgi2, SIZE[BcdDefs.SGRecord], @sgr2]; sb1 _ (sgr1.base-1)*INT[wordsPerPage]; sb2 _ (sgr2.base-1)*INT[wordsPerPage]; stats.symOff1 _ sb1; stats.symOff2 _ sb2; CompareWords[ IO.PutFR[ "In basic symbols for %g (module %g)\n", [rope[GetName[rope1, bcd1.ssOffset, mtr1.name]]], [integer[i]]], sb1, sb2, MIN[sgr1.pages, sgr2.pages]*wordsPerPage, stats]; stats.symOff1 _ stats.symOff2 _ 0; -- inhibit Diagnose CompareWords[ IO.PutFR[ "In extended symbols for %g (module %g)\n", [rope[GetName[rope1, bcd1.ssOffset, mtr1.name]]], [integer[i]]], sb1+sgr1.pages*wordsPerPage, sb2+sgr2.pages*wordsPerPage, MIN[sgr1.extraPages, sgr2.extraPages]*wordsPerPage, stats ]; }; mti1 _ mti1 + nw1; mti2 _ mti2 + nw2; ENDLOOP; }; IF stats.debug THEN { stats.maxTabLim1 _ stats.maxTabLim2 _ SIZE[BCD]; CompareWords[ "In whole file\n", stats.maxTabLim1, stats.maxTabLim2, MIN[len/bytesPerWord-stats.maxTabLim1, len/bytesPerWord-stats.maxTabLim2], stats]; }; SELECT stats.errors FROM 0 => {}; 1 => ERROR GiveUp["Too bad, only one little difference."]; ENDCASE => ERROR GiveUp[ IO.PutFR["%g differences encountered.", [integer[stats.errors]]]]; }; CompareWords: PROC [name: ROPE, offset1,offset2: INT, nWords: INT, stats: Stats] = TRUSTED { r1: ROPE = Rope.Substr[stats.rope1, 0, (offset1+nWords)*bytesPerWord]; lim1: INT = Rope.Length[r1]; r2: ROPE = Rope.Substr[stats.rope2, 0, (offset2+nWords)*bytesPerWord]; lim2: INT = Rope.Length[r2]; sth1,sth2: SymbolTableHeader _ NIL; off1: INT _ offset1*bytesPerWord; off2: INT _ offset2*bytesPerWord; IF stats.debug THEN IO.PutF[ stats.out, "** %g CompareWords[offset1: %g, offset2: %g, nWords: %g]\n", [rope[name]], [integer[offset1]], [integer[offset2]], [integer[nWords]]]; WHILE off1 < lim1 AND off2 < lim2 DO nc: INT = Rope.Run[r1, off1, r2, off2]; nOff1: INT _ off1+nc; nOff2: INT _ off2+nc; nwOff1,nwOff2: INT; w1,w2: Word; f1,f2: ROPE; which1,which2: ROPE _ NIL; IF nOff1 >= lim1 OR nOff2 >= lim2 THEN EXIT; IF name # NIL THEN {IO.PutRope[stats.out, name]; name _ NIL}; nwOff1 _ nOff1/bytesPerWord; nwOff2 _ nOff2/bytesPerWord; f1 _ Rope.Flatten[r1, nOff1 _ nwOff1*bytesPerWord, bytesPerWord]; w1 _ (LOOPHOLE[f1, WordPtr]+SIZE[TEXT])^; f2 _ Rope.Flatten[r2, nOff2 _ nwOff2*bytesPerWord, bytesPerWord]; w2 _ (LOOPHOLE[f2, WordPtr]+SIZE[TEXT])^; IF nOff1 = nOff2 THEN IO.PutF[stats.out, " at word offset %g", [integer[nwOff1]]] ELSE IO.PutF[ stats.out, " at word offsets (%g, %g)", [integer[nwOff1]], [integer[nwOff2]]]; IO.PutF[ stats.out, ", %b # %b (\"%q\" # \"%q\")\n", [cardinal[w1]], [cardinal[w2]], [rope[f1]], [rope[f2]]]; IF stats.symOff1 > 0 THEN { IF sth1 = NIL THEN { sth1 _ NEW[SymbolSegment.STHeader]; GetWordsToPtr[ stats.rope1, stats.symOff1, SIZE[SymbolSegment.STHeader], LOOPHOLE[sth1]]; }; which1 _ Diagnose[stats.rope1, sth1, offset1, nwOff1]; IO.PutRope[stats.out, which1]; IO.PutRope[stats.out, "\n"]; }; IF stats.symOff2 > 0 THEN { IF sth2 = NIL THEN { sth2 _ NEW[SymbolSegment.STHeader]; GetWordsToPtr[ stats.rope2, stats.symOff2, SIZE[SymbolSegment.STHeader], LOOPHOLE[sth2]]; }; which2 _ Diagnose[stats.rope2, sth2, offset2, nwOff2]; IF NOT which1.Equal[which2] THEN { IO.PutRope[stats.out, " (bcd1)\n"]; IO.PutRope[stats.out, which2]; IO.PutRope[stats.out, " (bcd2)\n"]; }; }; IF (stats.errors _ stats.errors + 1) > stats.maxErrors THEN { ERROR GiveUp["Too many differences encountered."]; }; off1 _ nOff1 + bytesPerWord; off2 _ nOff2 + bytesPerWord; ENDLOOP; }; CompareBytes: PROC [name: ROPE, offset1,offset2: INT, nBytes: INT, stats: Stats] = TRUSTED { r1: ROPE = Rope.Substr[stats.rope1, 0, offset1+nBytes]; lim1: INT = Rope.Length[r1]; r2: ROPE = Rope.Substr[stats.rope2, 0, offset2+nBytes]; lim2: INT = Rope.Length[r2]; IF stats.debug THEN IO.PutF[ stats.out, "** %g CompareBytes[offset1: %g, offset2: %g, nBytes: %g]\n", [rope[name]], [integer[offset1]], [integer[offset2]], [integer[nBytes]]]; WHILE offset1 < lim1 AND offset2 < lim2 DO nc: INT = Rope.Run[r1, offset1, r2, offset2]; nOff1: INT = offset1+nc; nOff2: INT = offset2+nc; f1,f2: ROPE; IF nOff1 >= lim1 OR nOff2 >= lim2 THEN EXIT; IF name # NIL THEN { IO.PutRope[stats.out, name]; name _ NIL; }; f1 _ Rope.Flatten[r1, nOff1, 1]; f2 _ Rope.Flatten[r2, nOff2, 1]; IF nOff1 = nOff2 THEN IO.PutF[ stats.out, " at byte offset %g", [integer[nOff1]]] ELSE IO.PutF[ stats.out, " at byte offsets (%g, %g)", [integer[nOff1]], [integer[nOff2]]]; IO.PutF[ stats.out, ", %b # %b ('%q # '%q)\n", [cardinal[f1.Fetch[0]-0C]], [cardinal[f2.Fetch[0]-0C]], [rope[f1]], [rope[f2]]]; IF (stats.errors _ stats.errors + 1) > stats.maxErrors THEN { ERROR GiveUp["Too many differences encountered."]; }; offset1 _ nOff1+1; offset2 _ nOff2+1; ENDLOOP; }; CompareEntries: PROC [name: ROPE, src1,src2: LONG POINTER, nWords: NAT, stats: Stats] = TRUSTED { WHILE nWords > 0 DO w1: Word = LOOPHOLE[src1, WordPtr]^; w2: Word = LOOPHOLE[src2, WordPtr]^; IF w1 # w2 THEN { IF name # NIL THEN { IO.PutRope[stats.out, name]; name _ NIL; }; IO.PutF[ stats.out, " difference at %g, %g # %g\n", [integer[src1-stats.base1]], [cardinal[w1]], [cardinal[w2]]]; IF (stats.errors _ stats.errors + 1) > stats.maxErrors THEN { ERROR GiveUp["Too many differences encountered."]; }; }; src1 _ src1 + 1; src2 _ src2 + 1; nWords _ nWords - 1; ENDLOOP; }; CompareTables: PROC [name: ROPE, ptr1,ptr2: LONG POINTER, stats: Stats, rt: BOOL _ FALSE] = TRUSTED { src1: WordPtr _ LOOPHOLE[ptr1, WordPtr]; offset1: CARDINAL _ LOOPHOLE[src1, WordPtr]^; len1: CARDINAL = (src1+1)^; lim1: CARDINAL = len1+offset1; src2: WordPtr _ LOOPHOLE[ptr2, WordPtr]; offset2: CARDINAL _ src2^; len2: CARDINAL = (src2+1)^; lim2: CARDINAL = len2+offset2; nWords: CARDINAL = MIN[lim1, lim2]; oldErrors: CARDINAL; rtOff1,rtOff2: INT _ 0; IF stats.debug THEN { IO.PutF[ stats.out, " %g, range1 = [%g, %g), range2 = [%g, %g).\n", [rope[name]], [integer[offset1]], [integer[lim1]], [integer[offset2]], [integer[lim2]]]; }; stats.maxTabLim1 _ MAX[stats.maxTabLim1, lim1]; stats.maxTabLim2 _ MAX[stats.maxTabLim2, lim2]; IF offset1 # offset2 THEN { IO.PutF[ stats.out, "Offsets for %g not equal, %g # %g\n", [rope[name]], [cardinal[offset1]], [cardinal[offset2]]]; IF (stats.errors _ stats.errors + 1) > stats.maxErrors THEN { ERROR GiveUp["Too many differences encountered."]; }; }; IF len1 # len2 THEN { IO.PutF[ stats.out, "Lengths for %g not equal, %g # %g\n", [rope[name]], [cardinal[len1]], [cardinal[len2]]]; IF (stats.errors _ stats.errors + 1) > stats.maxErrors THEN { ERROR GiveUp["Too many differences encountered."]; }; }; oldErrors _ stats.errors; IF rt THEN { rtOff1 _ LOOPHOLE[stats.base1, BcdPtr].rtPages.relPageBase*wordsPerPage; rtOff2 _ LOOPHOLE[stats.base2, BcdPtr].rtPages.relPageBase*wordsPerPage; }; CompareWords[ Rope.Cat["In ", name, "\n"], rtOff1+offset1, rtOff2+offset2, MIN[len1, len2], stats ! GiveUp => { stats.errors _ oldErrors+1; IO.PutRope[stats.out, "... too many differences for this table.\n"]; CONTINUE}]; }; GetWords: PROC [rope: ROPE, wordOffset: INT, nWords: NAT, buffer: Buffer] = TRUSTED { wordIndex: NAT _ 0; byteIndex: [0..bytesPerWord) _ 0; word: PACKED ARRAY [0..bytesPerWord) OF CHAR _ ALL[0C]; action: Rope.ActionType = TRUSTED { word[byteIndex] _ c; IF byteIndex = bytesPerWord-1 THEN { byteIndex _ 0; buffer[wordIndex] _ LOOPHOLE[word]; wordIndex _ wordIndex + 1} ELSE byteIndex _ byteIndex + 1; }; buffer.start _ wordOffset; buffer.len _ nWords; [] _ Rope.Map[rope, wordOffset*bytesPerWord, nWords*bytesPerWord, action]; }; GetWordsToPtr: UNSAFE PROC [rope: ROPE, wordOffset: INT, nWords: NAT, ptr: LONG POINTER] = TRUSTED { byteIndex: [0..bytesPerWord) _ 0; word: PACKED ARRAY [0..bytesPerWord) OF CHAR _ ALL[0C]; action: Rope.ActionType = TRUSTED { word[byteIndex] _ c; IF byteIndex = bytesPerWord-1 THEN { byteIndex _ 0; LOOPHOLE[ptr, WordPtr]^ _ LOOPHOLE[word]; ptr _ ptr + 1} ELSE byteIndex _ byteIndex + 1; }; [] _ Rope.Map[rope, wordOffset*bytesPerWord, nWords*bytesPerWord, action]; }; GetWord: PROC [rope: ROPE, wordOffset: INT] RETURNS [Word] = { byteIndex: NAT _ 0; word: PACKED ARRAY [0..bytesPerWord) OF CHAR _ ALL[0C]; action: Rope.ActionType = TRUSTED { word[byteIndex] _ c; byteIndex _ byteIndex + 1; }; [] _ Rope.Map[rope, wordOffset*bytesPerWord, bytesPerWord, action]; RETURN [LOOPHOLE[word]]; }; Diagnose: PROC [rope: ROPE, sth: SymbolTableHeader, base,offset: INT] RETURNS [which: ROPE _ NIL] = TRUSTED { ptr: LONG POINTER TO BlockDescriptor _ @sth.hvBlock; list: LIST OF ROPE _ blockList; fromBase: INT = offset-base; IF sth.fgPgCount # 0 THEN { fgOffset: INT = base+sth.fgRelPgBase*INT[wordsPerPage]; IF (fgOffset+SIZE[FGHeader])*bytesPerWord <= rope.Length[] THEN { fgHeader: FGHeader; inner: INT; GetWordsToPtr[rope, fgOffset, SIZE[FGHeader], @fgHeader]; inner _ offset - fgHeader.offset; IF inner >= 0 AND inner < fgHeader.length THEN RETURN [ IO.PutFR[ " at offset %g in fine grain table (%g)", [integer[fromBase]], [integer[inner]]]]; }; }; WHILE list # NIL DO inner: INT = fromBase - ptr.offset; IF inner >= 0 AND inner < ptr.size THEN RETURN [ IO.PutFR[ " at offset %g in %g (%g)", [integer[fromBase]], [rope[list.first]], [integer[inner]]]]; list _ list.rest; ptr _ ptr + SIZE[BlockDescriptor]; ENDLOOP; which _ IO.PutFR[" at offset %g in symbols ??", [integer[fromBase]]]; }; NameOut: PROC [rope: ROPE, base: CARDINAL, nameRecord: INT, stats: Stats] = { byteIndex: INT = base*bytesPerWord+nameRecord+4; length: CARDINAL = MIN[64, rope.Fetch[byteIndex-1]-0C]; action: Rope.ActionType = { IO.PutChar[stats.out, c]; }; [] _ Rope.Map[rope, byteIndex, length, action]; }; GetName: PROC [rope: ROPE, base: CARDINAL, nameRecord: INT] RETURNS [ROPE] = { byteIndex: INT = base*bytesPerWord+nameRecord+4; length: CARDINAL = MIN[64, rope.Fetch[byteIndex-1]-0C]; RETURN [Rope.Substr[rope, byteIndex, length]]; }; FilesOut: PROC [rope: ROPE, bcd: BcdPtr, stats: Stats] = TRUSTED { fti: CARDINAL _ LOOPHOLE[FIRST[BcdDefs.FTIndex]]; ftr: BcdDefs.FTRecord; WHILE fti < LOOPHOLE[bcd.ftLimit, CARDINAL] DO GetWordsToPtr[rope, fti+bcd.ftOffset, SIZE[BcdDefs.FTRecord], @ftr]; IO.PutF[stats.out, " file #%g: ", [integer[fti]]]; NameOut[rope, bcd.ssOffset, ftr.name, stats]; IO.PutRope[stats.out, ", {"]; VersionOut[ftr.version, stats, TRUE]; IO.PutRope[stats.out, "}\n"]; fti _ fti + SIZE[BcdDefs.FTRecord]; ENDLOOP; }; SegmentsOut: PROC [rope: ROPE, bcd: BcdPtr, stats: Stats] = TRUSTED { sgi: CARDINAL _ LOOPHOLE[FIRST[BcdDefs.SGIndex], CARDINAL]; sgr: BcdDefs.SGRecord; WHILE sgi < LOOPHOLE[bcd.sgLimit, CARDINAL] DO GetWordsToPtr[rope, sgi+bcd.sgOffset, SIZE[BcdDefs.SGRecord], @sgr]; IO.PutF[stats.out, " seg #%g", [integer[sgi]]]; SELECT sgr.class FROM code => IO.PutRope[stats.out, " (code)"]; symbols => IO.PutRope[stats.out, " (symbols)"]; acMap => IO.PutRope[stats.out, " (acMap)"]; other => IO.PutRope[stats.out, " (other)"]; ENDCASE => ERROR; SELECT sgr.file FROM BcdDefs.FTNull => IO.PutRope[stats.out, ", file: null"]; BcdDefs.FTSelf => IO.PutRope[stats.out, ", file: self"]; ENDCASE => IO.PutF[stats.out, ", file: %g", [integer[LOOPHOLE[sgr.file, CARDINAL]]]]; IO.PutF[ stats.out, ", base: %g, pages: %g, extraPages: %g\n", [integer[sgr.base]], [integer[sgr.pages]], [integer[sgr.extraPages]]]; sgi _ sgi + SIZE[BcdDefs.SGRecord]; ENDLOOP; }; VersionOut: PROC [version: VersionStamp, stats: Stats, stampOnly: BOOL _ FALSE] = { versionNibbles: PACKED ARRAY [0..12) OF [0..16) = LOOPHOLE[version]; FOR i: NAT IN [0..12) DO nibble: [0..16) _ versionNibbles[i]; IF nibble < 10 THEN IO.PutChar[stats.out, '0+nibble] ELSE IO.PutChar[stats.out, 'a+(nibble-10)]; ENDLOOP; IF stampOnly THEN RETURN; IF version.net # 0 OR version.host # 0 THEN IO.PutF[stats.out, " (%g, %g, ", [cardinal[version.net]], [cardinal[version.host]]] ELSE IO.PutRope[stats.out, " ("]; {ENABLE RuntimeError.UNCAUGHT => GO TO dreck; IO.PutF[ stats.out, "%g)", [time[BasicTime.FromNSTime[version.time]]] ]; EXITS dreck => IO.PutRope[stats.out, "??)"]; }; }; Commander.Register[ "CompareCode", DoCompare, "Compare the code of two bcd files, reporting the differences.", $Code]; Commander.Register[ "CompareBcd", DoCompare, "Compare two bcd files, reporting the differences.", $All]; Commander.Register[ "CompareSymbol", DoCompare, "Compare the symbols two bcd files, reporting the differences.", $Symbols]; Commander.Register[ "CompareDebug", DoCompare, "Compare two bcd files, reporting the differences.", $Debug]; END. ¶BcdCompare.mesa Russ Atkinson, October 26, 1983 3:44 pm T Y P E S & C O N S T A N T S E R R O R S F L A G S & V A R I A B L E S P R O C S [cmd: Handle] RETURNS [result: REF _ NIL, msg: Rope.ROPE _ NIL] Compare the code portions of this module. First, get the proper SGRecords for the code Finally, compare the code Compare the symbol portions of this module. First, get the proper SGRecords for the symbols Set the symbol offset in stats for use by Diagnose Compare the basic symbols Compare the extended symbols Try to determine which block it is in Try to determine which block it is in Different diagnoses for the two files! This table should be interpreted relative to the RTBcd extension Now compare the words within the table. First look at the fine grain table (if any). The difference is in the fine grain table Now try the block descriptors This next statement is separate to deal with potential errors in time conversion. Ê¿˜šœ™Jšœ'™'—J˜šÏk ˜ Jšœœ˜"Jšœ œ˜šœœ˜Jšœk˜n—Jšœ œ!˜0Jšœœ ˜JšœœGœ˜Yšœ˜ JšœMœ˜X—Jšœ œœ˜Jšœœ'˜:Jšœ œ˜Jšœœ˜J˜—šœ œ˜Jšœœ˜BJšœ˜J˜—šœ!™!J˜Jšœœ œ˜Jš œœœœœœ˜#Jšœœ!˜6Jšœœœ ˜Jšœ œœ œ œ œœœ˜ZJšœ œ˜(Jšœ œ˜&Jšœœœ˜Jšœœœ ˜šœ œœ˜Jšœ!œœ˜.Jšœ œœ˜Jšœ œœ˜Jšœ œœœ˜ Jšœœ˜Jšœœœ˜Jšœœœ˜Jšœ œ˜Jšœ œ˜Jšœœ˜Jšœ œ˜Jšœ˜—Jšœœœœ˜Jšœœœ˜6Jšœœ˜*Jšœœ˜Jš œ œœœœ˜%J˜Jšœœ˜(Jšœœœ˜$Jšœœ˜.—J˜šœ ™ J™Jšœœœœ˜!J˜—šœ™J™Jšœœ˜š œ œœœœ˜J˜Ð—J˜—šœ ™ J™šœ$˜$Jšœ?™?Jšœœœœ˜%Jšœ œ˜šœœœ˜%Jšœœœœ˜'—šœœœ˜%Jšœœœœ˜'—šœ˜Jšœ˜šœœœ ˜&Jšœ$œœ ˜5——Jšœ˜š˜Jšœ˜JšœE˜E—J˜J˜—šÏnœœ&œ˜GJšœœ@˜KJšœœ@˜KJšœœ ˜Jšœ/˜/Jšœ œ#œ!˜[Jšœ˜Jšœ˜Jšœ˜Jšœ˜Jšœ˜Jšœ(˜(J˜J˜—šžœœœ˜2šœœ˜šœœ˜ šœ˜Jšœœ˜Jšœœ˜Jšœœ˜#Jšœ&œ˜+Jšœ˜——šœœœœ˜šœœ˜Jšœ"˜"J˜Jšœ˜——Jšœ˜—J˜J˜—š žœœœœœœ˜?Jšœœ˜$šœœ˜Jšœ+œ˜8Jšœ˜#—Jšœ˜J˜J˜—šžœœœœ˜FJšœœ œœ˜,Jšœœ˜%Jšœœ œœ˜,Jšœœ˜%Jšœœœ!˜/Jšœœœ ˜'Jšœœœ ˜'Jšœ˜Jšœ˜J˜Jšœ!˜#Jšœ&˜(Jšœ œ˜&JšœH˜JJšœ2˜2Jšœ,˜.Jšœ&˜&Jšœ˜J˜Jšœ!˜#Jšœ&˜(Jšœ œ˜&JšœH˜JJšœ2˜2Jšœ,˜.Jšœ&˜&Jšœ˜J˜šœ!œ˜)Jšœ@˜BJ˜J˜—J˜šœ˜Jšœ˜Jšœ(œœ ˜?—šœ˜Jšœ˜Jšœœ˜9—šœ˜Jšœ.œ˜I—šœ˜Jšœ˜Jšœ*œ˜E—šœ˜Jšœ˜Jšœœ˜5—šœ˜Jšœ˜Jšœ$œœ ˜;—šœ˜Jšœ˜Jšœ œœ ˜7—šœ˜Jšœ˜Jšœ œœ ˜7—šœ˜Jšœ˜Jšœ œœ ˜7—šœ˜JšœZ˜ZJšœ$œœ ˜;—šœ˜Jšœ˜Jšœ œœ ˜7—Jšœ œœ#˜9šœ˜Jšœ7˜7—šœ˜Jšœ7˜7—šœ˜Jšœ7˜7—šœ˜Jšœ9˜9—šœ˜Jšœ9˜9—šœ˜JšœB˜B—šœ˜Jšœ8˜8—šœ˜Jšœ5˜5—šœ˜Jšœ6˜6—šœ˜Jšœ5˜5—šœ˜Jšœ7˜7—šœ˜Jšœ9˜9—šœ˜Jšœ;˜;—šœœœ˜)šœ˜Jšœ>œ˜D—šœ˜JšœEœ˜K—šœ˜Jšœ>œ˜D—šœ˜Jšœ.œœ ˜E—J˜—šœ œ˜Jšœ0˜2J˜ Jšœ0˜2J˜ J˜—šœ œ˜Jšœ-˜/J˜Jšœ-˜/J˜J˜—šœÏc*˜+Jš œœœœœ˜JJš œœœœœ˜Jš œœœœ˜6Jšœ˜Jšœ˜Jšœ˜Jšœ˜Jšœœ˜Jšœœ˜Jšœ œ˜ Jšœœ˜:Jšœœ˜:šœ œ˜Jšœœ&œ˜MJšœœ˜3Jšœœ˜3Jšœœ˜—šœ œ˜Jšœœ&œ˜MJšœœ˜3Jšœœ˜3Jšœœ˜—šœœ œ˜%Jšœ)™)J™JšŸ,™,Jšœœœ˜9Jšœœœ˜9Jšœœ˜:Jšœœ˜:Jšœœ˜&Jšœœ˜&Jšœ/˜/Jšœ/˜/J˜šœœ˜šœœ˜0Jšœ"˜$—šœ˜šœ˜Jšœ8˜8Jšœ˜——šœ˜šœ˜Jšœ8˜8Jšœ˜——šœ˜ Jšœ™šœ ˜ šœ˜ Jšœ˜Jšœ1˜1Jšœ˜—Jšœœ-˜D———J˜—šœœ œ˜(Jšœ+™+J™JšŸ/™/Jšœœ œ˜5Jšœœ œ˜5Jšœœ˜:Jšœœ˜:Jšœœ˜&Jšœœ˜&J™Jšœ2™2Jšœ˜Jšœ˜J˜Jšœ™šœ ˜ šœ˜ Jšœ(˜(Jšœ@˜@—Jšœ œ.˜;—J˜Jšœ™Jšœ$Ÿ˜7šœ ˜ šœ˜ Jšœ+˜+Jšœ1˜1Jšœ˜—Jšœ˜Jšœ˜Jšœ0˜3J˜J˜—J˜—J˜J˜Jšœ˜—J˜—šœ œ˜Jšœ&œœ˜0šœ ˜ Jšœ˜Jšœ#˜#JšœG˜JJšœ˜—J˜—šœ˜J˜Jšœœ0˜:šœ˜ šœ˜ Jšœ@˜B———Jšœ˜J˜—šž œ˜Jš œœœ œœ˜IJšœœ>˜FJšœœ˜Jšœœ>˜FJšœœ˜Jšœœ˜#Jšœœ˜!Jšœœ˜!šœ ˜šœ˜JšœI˜IJšœI˜I——šœ œ ˜$Jšœœ ˜'Jšœœ ˜Jšœœ ˜Jšœœ˜J˜ Jšœœ˜ Jšœœœ˜Jšœœœœ˜,Jš œœœœ"œ˜=Jšœ˜Jšœ˜JšœA˜AJšœœœœ˜)JšœA˜AJšœœœœ˜)šœ˜Jšœœ;˜Bšœœ˜ JšœP˜P——šœ˜Jšœ ˜ Jšœ ˜ Jšœ8˜8—šœœ˜šœœœ˜Jšœœ˜#˜Jšœœœ˜J—J˜—Jšœ%™%Jšœ6˜6Jšœ˜Jšœ˜Jšœ˜—šœœ˜šœœœ˜Jšœœ˜#˜Jšœœœ˜J—J˜—Jšœ%™%Jšœ6˜6šœœœ˜"Jšœ&™&Jšœ!˜#Jšœ˜Jšœ!˜#J˜—J˜—šœ5œ˜=Jšœ-˜2J˜—Jšœ˜Jšœ˜Jšœ˜—J˜J˜—šž œ˜Jš œœœ œœ˜IJšœœ/˜7Jšœœ˜Jšœœ/˜7Jšœœ˜šœ ˜šœ˜JšœI˜IJšœI˜I——šœœ˜*Jšœœ&˜-Jšœœ˜Jšœœ˜Jšœœ˜ Jšœœœœ˜,šœœœ˜Jšœ˜Jšœœ˜ J˜—Jšœ ˜ Jšœ ˜ šœ˜š˜šœ˜Jšœ ˜ Jšœ˜Jšœ˜——š˜šœ˜Jšœ ˜ Jšœ˜Jšœ$˜$———šœ˜Jšœ ˜ Jšœ˜JšœP˜P—šœ5œ˜=Jšœ-˜2J˜—J˜J˜Jšœ˜—J˜J˜—šžœ˜Jš œœ œœ œœ˜Lšœ ˜Jšœ œ˜$Jšœ œ˜$šœ œ˜šœœœ˜Jšœ˜Jšœœ˜ J˜—šœ˜Jšœ ˜ Jšœ!˜!Jšœ=˜=—šœ5œ˜=Jšœ-˜2J˜—J˜—Jšœ˜Jšœ˜Jšœ˜Jšœ˜—J˜J˜—šž œ˜Jš œœ œœœœœ˜QJšœœ˜(Jšœ œœ˜-Jšœœ ˜Jšœœ˜Jšœœ˜(Jšœ œ ˜Jšœœ ˜Jšœœ˜Jšœœœ ˜#Jšœ œ˜Jšœœ˜šœ œ˜šœ˜Jšœ;˜;JšœX˜X—J˜—Jšœœ˜/Jšœœ˜/šœœ˜šœ˜Jšœ ˜ Jšœ&˜&Jšœ8˜8—šœ5œ˜=Jšœ-˜2J˜—J˜—šœ œ˜šœ˜Jšœ ˜ Jšœ&˜&Jšœ2˜2—šœ5œ˜=Jšœ-˜2J˜—J˜—J˜šœœ˜ Jšœ@™@Jšœ œ7˜HJšœ œ7˜HJ˜—Jšœ'™'šœ ˜ Jšœ˜Jšœ œ˜6šœ ˜ Jšœ˜JšœB˜DJšœ˜ ——J˜J˜—š žœœœœ œœ˜UJšœ œ˜Jšœ!˜!Jš œœœœœœ˜7šœœ˜#Jšœ˜šœ˜šœ˜Jšœ˜Jšœœ˜#Jšœ˜—š˜Jšœ˜——J˜—Jšœ˜Jšœ˜JšœJ˜JJ˜——˜šž œœ˜Jš œœœ œœœœ˜IJšœ!˜!Jš œœœœœœ˜7šœœ˜#Jšœ˜šœ˜šœ˜Jšœ˜Jšœœ˜)Jšœ˜—š˜Jšœ˜——J˜—JšœJ˜JJ˜J˜—š žœœœœœ ˜>Jšœ œ˜Jš œœœœœœ˜7šœœ˜#Jšœ˜Jšœ˜J˜—JšœC˜CJšœœ˜J˜J˜—šžœ˜Jšœœ'œ˜6Jšœ œœœ˜'Jšœœœœ ˜4Jšœœœœ ˜Jšœ œ˜Jšœ,™,šœœ˜Jšœ œœ˜7šœ œ*œ˜AJ˜Jšœœ˜ Jšœœ˜9Jšœ!˜!šœ œ˜.Jšœ)™)šœ˜šœ˜ Jšœ/˜/Jšœ(˜(———J˜—J˜—Jšœ™šœœ˜Jšœœ˜#šœ œ˜'šœ˜šœ˜ Jšœ ˜ Jšœ<˜<———J˜Jšœ œ˜"Jšœ˜—Jšœœ>˜HJšœ˜J˜—š žœœœœœ˜MJšœ œ"˜0Jšœœœ!˜7šœ˜Jšœ˜J˜—Jšœ/˜/J˜J˜—šžœœœœœœœ˜NJšœ œ"˜0Jšœœœ!˜7Jšœ(˜.J˜J˜—šžœœœœ˜BJšœœœœ˜1Jšœ˜šœœœ˜.Jšœ&œ˜DJšœ1˜3Jšœ-˜-Jšœ˜Jšœœ˜%Jšœ˜Jšœ œ˜#Jšœ˜—Jšœ˜J˜—šž œœœœ˜EJš œœœœœ˜;Jšœ˜šœœœ˜.Jšœ&œ˜DJšœ.˜0šœ ˜Jšœœ˜)Jšœ œ"˜/Jšœ œ ˜+Jšœ œ ˜+Jšœœ˜—šœ ˜šœ˜Jšœ$˜&—šœ˜Jšœ$˜&—šœ˜ Jšœ(œ œ˜J——šœ˜Jšœ5˜5JšœF˜F—Jšœ œ˜#Jšœ˜—Jšœ˜J˜—šž œœ2œœ˜SJš œœœ œ œ ˜Dšœœœ ˜Jšœ$˜$šœ ˜Jšœœ˜%Jšœœ$˜+—Jšœ˜—Jšœ œœ˜šœœ˜&JšœœQ˜XJšœœ˜!—JšœQ™Qš œœœœœ˜-šœ˜Jšœ˜Jšœ*˜*Jšœ˜—š˜Jšœ œ˜&—J˜—J˜—J˜—˜J˜J˜H—˜J˜J˜;—˜J˜JšœK˜K—˜J˜Jšœ=˜=—J˜Jšœ˜J˜—…—W8v­