DIRECTORY BasicTime USING [Now], Commander USING [CommandProc, Register], CommanderOps USING [ArgumentVector, Failed, Parse], EditSpan USING [Copy], FileNames USING [ResolveRelativePath], FS USING [defaultStreamOptions, Error, FileInfo, StreamOpen, StreamOptions], IO USING [Close, EndOfStream, GetBlock, GetCedarToken, GetCedarTokenRope, GetChar, GetIndex, noWhereStream, PeekChar, Put, PutChar, PutF, PutRope, RIS, RopeFromROS, ROS, SetIndex, SkipWhitespace, STREAM, TokenKind], NodeProps USING [PutProp], Process USING [CheckForAbort], PutGet USING [FromFile, WritePlain], RefText USING [AppendRope, Equal, Fetch, InlineAppendChar, Length, TrustTextAsRope], Rope USING [Cat, Concat, Equal, Fetch, Flatten, FromRefText, Length, Match, ROPE], SymTab USING [Create, EachPairAction, Fetch, FetchText, Insert, Pairs, Ref], TextNode USING [LastWithin, Level, MakeNodeLoc, MakeNodeSpan, NodeRope, Ref, StepForward], TiogaFileOps USING [AddLooks, CreateRoot, InsertAsLastChild, Ref, SetContents, Store]; Waterlily: CEDAR PROGRAM IMPORTS BasicTime, Commander, CommanderOps, EditSpan, FileNames, FS, IO, NodeProps, Process, PutGet, RefText, Rope, SymTab, TextNode, TiogaFileOps = { ROPE: TYPE = Rope.ROPE; STREAM: TYPE = IO.STREAM; SymbolTableEntry: TYPE = REF SymbolTableEntryRep; SymbolTableEntryRep: TYPE = RECORD[ oldList: InstanceList, -- the old instances newList: InstanceList, -- the new instances key: ROPE -- the key used for the lookup ]; InstanceList: TYPE = LIST OF InstanceRep; InstanceRep: TYPE = RECORD [ line: INT, -- -1 => not yet assigned pos: INT, -- -1 => not yet assigned (node number if mergeFiles) node: TextNode.Ref_NIL, -- the node, if mergeFiles, instead of line len: NAT, -- length of original token peek: CHAR -- non-blank character after this token ]; FileArray: TYPE = REF FileArrayRep; FileArrayRep: TYPE = RECORD [entry: SEQUENCE index: NAT OF FileArrayEntry]; FileArrayEntry: TYPE = REF FileArrayEntryRep; FileArrayEntryRep: TYPE = RECORD [ symEntry: SymbolTableEntry, instance: InstanceList, otherIndex: INT, node: TextNode.Ref_NIL, typeOfPntr: {symTable, lineNum}, len: NAT _ 0]; Ref: TYPE = TextNode.Ref; Node: TYPE = REF NodeBody; NodeBody: TYPE = RECORD [root: Ref_NIL, node: Ref_NIL ]; LongHelpMsgW: ROPE = "Waterlily compares two source files. The command format is one of: Waterlily file1 file2 Waterlily difFile _ file1 file2 where switches are syntactically before any argument. Differences found are written on the difFile, with default extension '.dif'. The available switches are: t Tioga format files (default: TRUE) b Bravo format files (default: FALSE) u Unformatted files i Ignore blank lines (default: TRUE) s Strip digits trailing a _ char (for c2c) x Output file is a merger of input files (ran out of mnemonics already!) p Treat Tioga file as plain text (ie, compare comments too) Input files must be Tioga-format files. #m # of matching lines (default: 3) #c # of trailing context lines (default: 1) "; LongHelpMsgC: ROPE = "CedarLily compares two Cedar-program source files. Comparison is made at the source-language token level, so that only lexical differences will be found (formatting changes and modified comments will not affect the comparison). The command format is one of: CedarLily file1 file2 CedarLily difFile _ file1 file2 where switches are syntactically before any argument. Differences found are written on the difFile, with default extension '.dif'. The available switches are: u Unformatted files i Ignore blank lines (default: TRUE) p Treat Tioga file as plain text (ie, compare comments too) #m # of matching lines (default: 3) #c # of trailing context lines (default: 1) "; LongHelpMsgM: ROPE = "Tigerlily produces a merged version of two Tioga-format files. Nodes unique to file1 are included and indicated by overstriking. Nodes unique to file2 are included and indicated by underlining. Nodes that are common to both files are unchanged. The command format is one of: Tigerlily file1 file2 Tigerlily mergedFile _ file1 file2 where switches are syntactically before any argument. The merged file is written on the mergedFile, with default extension '.merger'. The available switches are: p Treat Tioga file as plain text (ie, compare comments too) #m # of matching lines (default: 3) #c # of trailing context lines (default: 1) "; repeats: NAT _ 1; debugging: BOOL _ FALSE; WaterlilyProc: Commander.CommandProc = { Alarm: ERROR = CODE; oldArray: FileArray; newArray: FileArray; out: STREAM _ cmd.out; pData: REF _ cmd.procData.clientData; totalNewLines: INT _ 0; totalOldLines: INT _ 0; posInNewFile: INT _ 0; posInOldFile: INT _ 0; nodeCount: INT _ 0; newFile: REF; -- IO.STREAM or Node; oldFile: REF; -- IO.STREAM or Node; difFile: STREAM; difFileNode: Node _ NIL; newFileName: ROPE _ NIL; oldFileName: ROPE _ NIL; difFileName: ROPE _ NIL; Asterisks: ROPE = "**************************************"; filler: ROPE = "->->->->->->"; FileType: TYPE = {tioga, bravo, unform}; switchNewFileType, switchOldFileType: FileType _ tioga; switchIgnoreEmptyLinesNewFile, switchIgnoreEmptyLinesOldFile: BOOL _ TRUE; switchTokens: BOOL _ FALSE; switchMergeFiles: BOOL _ FALSE; stripLeadingBlanks: BOOL _ FALSE; stripDigitsTrailingArrow: BOOL _ FALSE; switchLinesForMatch: NAT _ 3; switchLinesForContext: NAT _ 1; anyDifferencesSeen: BOOL _ FALSE; indexN: INT; indexO: INT; LineType: TYPE = {new, old, both}; Vintage: TYPE = LineType[new..old]; SetSymbolTableEntry: PROC [key: ROPE, node: TextNode.Ref, newOrOld: Vintage, line: INT, pos: INT, len: NAT, peek: CHAR] = { symTabEntry: SymbolTableEntry _ NIL; list: InstanceList _ LIST[[line: line, pos: pos, len: len, node: node, peek: peek]]; WITH SymTab.Fetch[symbolTable, key].val SELECT FROM x: SymbolTableEntry => symTabEntry _ x; ENDCASE => { symTabEntry _ NEW[SymbolTableEntryRep _ [ oldList: NIL, newList: NIL, key: key]]; [] _ SymTab.Insert[symbolTable, key, symTabEntry]; }; SELECT newOrOld FROM new => { list.rest _ symTabEntry.newList; symTabEntry.newList _ list; }; old => { list.rest _ symTabEntry.oldList; symTabEntry.oldList _ list; }; ENDCASE => ERROR; }; PruneList: PROC [list: InstanceList, pos: INT] RETURNS [pruned: InstanceList] = { IF list = NIL THEN RETURN [NIL]; IF list.first.pos = pos THEN RETURN [list.rest]; pruned _ list; DO lag: InstanceList _ list; list _ list.rest; IF list = NIL THEN RETURN; IF list.first.pos = pos THEN {lag.rest _ list.rest; RETURN}; ENDLOOP; }; ConnectEntries: PROC [symTabEntry: SymbolTableEntry, indexO, indexN: INT, entryO, entryN: FileArrayEntry] = { entryN.typeOfPntr _ entryO.typeOfPntr _ lineNum; entryN.otherIndex _ indexO; entryO.otherIndex _ indexN; symTabEntry.newList _ PruneList[symTabEntry.newList, entryN.instance.first.pos]; symTabEntry.oldList _ PruneList[symTabEntry.oldList, entryO.instance.first.pos]; }; EndOfFile: ERROR = CODE; token: REF TEXT _ NEW[TEXT[128]]; GetLine: PROC [stream: STREAM, token: REF TEXT] RETURNS [REF TEXT] = { token.length _ 0; DO c: CHAR; IF lineBufferPos >= lineBufferLen THEN { lineBuffer.length _ 0; lineBufferLen _ IO.GetBlock[stream, lineBuffer, 0, lineBufferSize ! IO.EndOfStream => EXIT]; IF lineBufferLen = 0 THEN { IF token.length = 0 THEN ERROR IO.EndOfStream[stream]; EXIT; }; lineBuffer.length _ lineBufferLen; lineBufferPos _ 0; }; c _ lineBuffer[lineBufferPos]; lineBufferPos _ lineBufferPos + 1; inputPos _ inputPos + 1; IF IsEndOfLine[c] THEN EXIT; token _ RefText.InlineAppendChar[token, c]; ENDLOOP; RETURN [token]; }; lineBufferSize: NAT _ 1024; lineBuffer: REF TEXT _ NEW[TEXT[lineBufferSize]]; lineBufferPos: NAT _ 0; lineBufferLen: NAT _ 0; inputPos: INT _ 0; ReadLineFromFile: PROC [source: REF, localFileType: FileType, localIgnoreEmpties: BOOL] RETURNS [key: ROPE, node: TextNode.Ref, peek: CHAR, pos: INT, len: NAT] = { SetToken: PROC [value: ROPE, append: BOOL _ FALSE] = { IF NOT append THEN token.length _ 0; token _ RefText.AppendRope[token, value]; }; in: STREAM; inNode: Node; WITH source SELECT FROM str: STREAM => in _ str; ref: Node => inNode _ ref; ENDCASE => ERROR; key _ NIL; node _ NIL; pos _ -1; len _ 0; peek _ 0C; DO Process.CheckForAbort[]; SELECT pData FROM $Cedar => { kind: IO.TokenKind; token.length _ 0; [] _ IO.SkipWhitespace[stream: in, flushComments: TRUE ! IO.EndOfStream => CONTINUE]; pos _ IO.GetIndex[in]; [tokenKind: kind, token: token, charsSkipped: ] _ IO.GetCedarToken[in, token ! IO.EndOfStream => ERROR EndOfFile]; IF kind = tokenEOF THEN ERROR EndOfFile; len _ IO.GetIndex[in] - pos; SELECT kind FROM tokenROPE => { len: NAT ~ RefText.Length[token]; lastChar: CHAR ~ IF ( len # 0 ) THEN RefText.Fetch[token, len.PRED] ELSE 0C; SELECT lastChar FROM 'L => { token.length _ len.PRED }; -- disregard frame specifiers for strings! 'G => { token.length _ len.PRED }; -- disregard frame specifiers for strings! ENDCASE; }; tokenSINGLE => { char: CHAR _ token[0]; SELECT char FROM '_ => token[0] _ '¬; -- Character code finesse '^ => token[0] _ '­; -- Character code finesse '; => LOOP; '} => { [] _ IO.SkipWhitespace[stream: in, flushComments: TRUE ! IO.EndOfStream => CONTINUE]; peek _ IO.PeekChar[in ! IO.EndOfStream => {peek _ 0C; CONTINUE}]; IF peek = '. THEN ERROR EndOfFile; }; ENDCASE; }; tokenID => { char: CHAR _ token[0]; [] _ IO.SkipWhitespace[stream: in, flushComments: TRUE ! IO.EndOfStream => CONTINUE]; peek _ IO.PeekChar[in ! IO.EndOfStream => {peek _ 0C; CONTINUE}]; SELECT char FROM 'B => SELECT TRUE FROM RefText.Equal[token, "BEGIN"] => SetToken["{"]; RefText.Equal[token, "BOOLEAN"] => SetToken["BOOL"]; ENDCASE; 'C => SELECT TRUE FROM RefText.Equal[token, "CHARACTER"] => SetToken["CHAR"]; RefText.Equal[token, "CARD"] => SetToken["CARD32"]; ENDCASE; 'E => SELECT TRUE FROM RefText.Equal[token, "END"] => { SetToken["}"]; IF peek = '. THEN ERROR EndOfFile; }; ENDCASE; 'I => SELECT TRUE FROM RefText.Equal[token, "INT"] => SetToken["INT32"]; ENDCASE; 'L => SELECT TRUE FROM RefText.Equal[token, "LONG"] => { key _ IO.GetCedarTokenRope[in].token; SELECT TRUE FROM Rope.Equal[key, "CARDINAL"] => SetToken["CARD32"]; Rope.Equal[key, "INTEGER"] => SetToken["INT32"]; ENDCASE => {SetToken["LONG "]; SetToken[key, TRUE]}; }; ENDCASE; 'P => SELECT TRUE FROM RefText.Equal[token, "PROCEDURE"] => SetToken["PROC"]; ENDCASE; ENDCASE; SELECT peek FROM '_ => { ch: CHAR _ IO.GetChar[in]; peek _ '¬; }; '^ => { ch: CHAR _ IO.GetChar[in]; peek _ '­; }; ':, '¬, '­, '., ',, '~ => { peek _ IO.GetChar[in]; }; ENDCASE => GO TO noHack; token _ RefText.InlineAppendChar[token, peek]; len _ IO.GetIndex[in] - pos; EXITS noHack => {}; }; ENDCASE; WITH SymTab.FetchText[symbolTable, token].val SELECT FROM symTabEntry: SymbolTableEntry => key _ symTabEntry.key; ENDCASE => key _ Rope.FromRefText[token]; EXIT; }; ENDCASE; IF switchMergeFiles THEN { pos _ nodeCount; nodeCount _ nodeCount+1; node _ inNode.node _ inNode.node.StepForward[]; IF node = NIL THEN ERROR EndOfFile; token.length _ 0; token _ RefText.AppendRope[token, node.NodeRope[]]; } ELSE { pos _ inputPos; token _ GetLine[in, token ! IO.EndOfStream => ERROR EndOfFile]; len _ token.length; }; IF stripDigitsTrailingArrow OR stripLeadingBlanks OR localFileType = bravo THEN { srcPos: NAT _ 0; dstPos: NAT _ 0; tLen: NAT = token.length; IF stripLeadingBlanks THEN WHILE srcPos < tLen DO SELECT token[srcPos] FROM ' , '\t => srcPos _ srcPos + 1; ENDCASE => EXIT; ENDLOOP; IF stripDigitsTrailingArrow OR localFileType = bravo THEN { skipDigits: BOOL _ FALSE; WHILE srcPos < tLen DO c: CHAR _ token[srcPos]; srcPos _ srcPos + 1; SELECT c FROM '_ => skipDigits _ stripDigitsTrailingArrow; IN ['0..'9] => IF skipDigits THEN LOOP; '\032 => IF localFileType = bravo THEN EXIT; ENDCASE => skipDigits _ FALSE; token[dstPos] _ c; dstPos _ dstPos + 1; ENDLOOP; }; len _ srcPos; IF stripLeadingBlanks THEN WHILE dstPos # 0 DO SELECT token[dstPos-1] FROM ' , '\t => dstPos _ dstPos - 1; ENDCASE => EXIT; ENDLOOP; token.length _ dstPos; }; WITH SymTab.FetchText[symbolTable, token].val SELECT FROM symTabEntry: SymbolTableEntry => key _ symTabEntry.key; ENDCASE => key _ Rope.FromRefText[token]; IF localIgnoreEmpties THEN { FOR i: NAT IN [0..token.length) DO SELECT token[i] FROM ' , '\t => {}; ENDCASE => GO TO Gotit; ENDLOOP; peek _ peek; } ELSE GOTO Gotit; ENDLOOP; len _ len; EXITS Gotit => pos _ pos }; FinishUp: PROC [difMsg: ROPE] = { IO.PutRope[out, difMsg]; IO.PutRope[out, "\n"]; IF switchMergeFiles THEN RETURN; IF difFile = NIL THEN OpenDifFileAndWriteHeader[]; IO.PutRope[difFile, difMsg]; IO.PutRope[difFile, "\n"]; IO.Close[difFile]; }; WorkingMsg: PROC [char: CHAR] = { Process.CheckForAbort[]; IO.PutChar[out, IF debugging THEN char ELSE '.]; }; OpenDifFileAndWriteHeader: PROC = { IF anyDifferencesSeen THEN RETURN; anyDifferencesSeen _ TRUE; difFileName _ DefaultExtension[difFileName, IF switchMergeFiles THEN ".merger" ELSE ".dif", TRUE]; IF switchMergeFiles THEN { difFile _ IO.noWhereStream; difFileNode _ NewNode[]; RETURN; }; difFile _ FS.StreamOpen[difFileName, $create]; IO.PutRope[difFile, IF pData = $Cedar THEN "\nCedarlily" ELSE "\nWaterlily"]; IO.PutF[difFile, "\n run on %g\n File 1: %g\n File 2: %g\n\n", [time[BasicTime.Now[]]], [rope[oldFileName]], [rope[newFileName]]]; }; OpenFile: PROC [tempFileName: ROPE, switchFileType: FileType, writePlain: BOOL] RETURNS [fileName: ROPE, file: REF] = { streamOptions: FS.StreamOptions _ FS.defaultStreamOptions; streamOptions[tiogaRead] _ (switchFileType = tioga); tempFileName _ DefaultExtension[tempFileName, ".mesa", FALSE]; fileName _ FS.FileInfo[tempFileName].fullFName; SELECT TRUE FROM switchMergeFiles => file _ NodeFromFile[fileName]; writePlain => { root: TextNode.Ref _ PutGet.FromFile[fileName]; s: IO.STREAM _ IO.ROS[]; PutGet.WritePlain[s, root]; file _ IO.RIS[IO.RopeFromROS[s]]; }; ENDCASE => file _ FS.StreamOpen[fileName, $read, streamOptions]; }; symbolTable: SymTab.Ref _ SymTab.Create[mod: 1023, case: TRUE]; fillerNode: Node _ NewNode[]; fillerNode.node _ TR[TiogaFileOps.InsertAsLastChild[FR[fillerNode.root]]]; TiogaFileOps.SetContents[FR[fillerNode.node], filler]; TiogaFileOps.AddLooks[FR[fillerNode.node], 0, filler.Length[], 'b, FR[fillerNode.root]]; NodeProps.PutProp[fillerNode.node, $Comment, NEW[BOOL_TRUE]]; result _ NIL; msg _ NIL; { args: CommanderOps.ArgumentVector _ CommanderOps.Parse[cmd ! CommanderOps.Failed => {msg _ "Syntax error."; GO TO fatalError} ]; fileCount: NAT _ 0; writePlain: BOOL _ FALSE; defaultFileType: FileType _ tioga; ignoreEmptyLines: BOOL _ TRUE; IF pData=$Merge THEN { switchMergeFiles _ TRUE; ignoreEmptyLines _ FALSE; }; FOR i: NAT IN [1..args.argc) DO arg: ROPE = args[i]; sense: BOOL _ TRUE; IF Rope.Match["-*", arg] THEN { len: NAT _ Rope.Length[arg]; number: INT _ 0; FOR i: NAT IN [1..len) DO c: CHAR _ Rope.Fetch[arg, i]; SELECT c FROM '~ => sense _ NOT sense; 'b, 'B => defaultFileType _ bravo; 't, 'T => defaultFileType _ tioga; 'u, 'U => defaultFileType _ unform; 'i, 'I => ignoreEmptyLines _ sense; 's, 'S => stripDigitsTrailingArrow _ stripLeadingBlanks _ sense; 'x, 'X => { switchMergeFiles _ sense; IF sense THEN ignoreEmptyLines _ FALSE; }; IN ['0..'9] => {number _ number*10 + (c-'0); LOOP}; 'm, 'M => IF number >= 1 THEN switchLinesForMatch _ number; 'c, 'C => IF number >= 1 THEN switchLinesForContext _ number; 'p, 'P => writePlain _ TRUE; ENDCASE; number _ 0; ENDLOOP; LOOP; }; IF Rope.Match["_", arg] THEN { IF fileCount # 1 THEN GO TO usageError; fileCount _ 0; difFileName _ oldFileName; LOOP; }; SELECT fileCount FROM 0 => { fileCount _ 1; switchOldFileType _ defaultFileType; switchIgnoreEmptyLinesOldFile _ ignoreEmptyLines; oldFileName _ FileNames.ResolveRelativePath[arg]; IF difFileName = NIL THEN difFileName _ ShortName[arg]; }; 1 => { fileCount _ 2; switchNewFileType _ defaultFileType; switchIgnoreEmptyLinesNewFile _ ignoreEmptyLines; newFileName _ FileNames.ResolveRelativePath[arg]; }; ENDCASE => {GO TO usageError}; ENDLOOP; IF fileCount # 2 THEN GO TO usageError; out.PutRope["Comparing "]; { ENABLE FS.Error => { IF error.group # bug THEN msg _ error.explanation; GO TO fatalError; }; [oldFileName, oldFile] _ OpenFile[oldFileName, switchOldFileType, writePlain]; [newFileName, newFile] _ OpenFile[newFileName, switchNewFileType, writePlain]; }; WorkingMsg['-]; }; { nextLine: ROPE _ NIL; nextNode: TextNode.Ref _ NIL; peek: CHAR; inputPos _ 0; lineBufferLen _ 0; lineBufferPos _ 0; DO key: ROPE; len: NAT; [key, nextNode, peek, posInNewFile, len] _ ReadLineFromFile[newFile, switchNewFileType, switchIgnoreEmptyLinesNewFile ! EndOfFile => EXIT]; SetSymbolTableEntry[key, nextNode, new, totalNewLines, posInNewFile, len, peek]; totalNewLines _ totalNewLines + 1; ENDLOOP; IF totalNewLines = 0 THEN GOTO emptyfile; newArray _ NEW[FileArrayRep[totalNewLines]]; WorkingMsg['!]; inputPos _ 0; lineBufferLen _ 0; lineBufferPos _ 0; DO key: ROPE; len: NAT; [key, nextNode, peek, posInOldFile, len] _ ReadLineFromFile[oldFile, switchOldFileType, switchIgnoreEmptyLinesOldFile ! EndOfFile => EXIT]; SetSymbolTableEntry[key, nextNode, old, totalOldLines, posInOldFile, len, peek]; totalOldLines _ totalOldLines + 1; ENDLOOP; IF totalOldLines = 0 THEN GOTO emptyfile; oldArray _ NEW[FileArrayRep[totalOldLines]]; WorkingMsg['@]; { Test: SymTab.EachPairAction = { symTabEntry: SymbolTableEntry _ NARROW[val]; newList: InstanceList _ symTabEntry.newList; oldList: InstanceList _ symTabEntry.oldList; FOR each: InstanceList _ newList, each.rest WHILE each # NIL DO newArray[each.first.line] _ NEW[FileArrayEntryRep _ [ symEntry: symTabEntry, instance: each, otherIndex: -1, node: each.first.node, typeOfPntr: symTable, len: each.first.len]]; ENDLOOP; FOR each: InstanceList _ oldList, each.rest WHILE each # NIL DO oldArray[each.first.line] _ NEW[FileArrayEntryRep _ [ symEntry: symTabEntry, instance: each, otherIndex: -1, node: each.first.node, typeOfPntr: symTable, len: each.first.len]]; ENDLOOP; RETURN[FALSE]; }; [] _ SymTab.Pairs[symbolTable, Test]; WorkingMsg['#]; }; EXITS emptyfile => { FinishUp["At least one of these files is effectively empty."]; RETURN; }; }; THROUGH [0..repeats) DO { Test: SymTab.EachPairAction = { symTabEntry: SymbolTableEntry _ NARROW[val]; newList: InstanceList _ symTabEntry.newList; oldList: InstanceList _ symTabEntry.oldList; Process.CheckForAbort[]; SELECT TRUE FROM newList = NIL, oldList = NIL => {}; newList.rest # NIL, oldList.rest # NIL => { }; ENDCASE => { indexO _ oldList.first.line; indexN _ newList.first.line; ConnectEntries[symTabEntry, indexO, indexN, oldArray[indexO], newArray[indexN]]; }; RETURN[FALSE]; }; [] _ SymTab.Pairs[symbolTable, Test]; WorkingMsg['$]; }; { indexN _ 0; WHILE indexN < totalNewLines DO entry: FileArrayEntry = newArray[indexN]; Process.CheckForAbort[]; indexN _ indexN + 1; IF entry.typeOfPntr = lineNum THEN { indexO _ entry.otherIndex + 1; WHILE indexN < totalNewLines AND indexO < totalOldLines DO entryN: FileArrayEntry = newArray[indexN]; entryO: FileArrayEntry = oldArray[indexO]; symEntry: SymbolTableEntry _ entryN.symEntry; SELECT TRUE FROM entryN.typeOfPntr = symTable AND entryO.typeOfPntr = symTable AND symEntry = entryO.symEntry => ConnectEntries[symEntry, indexO, indexN, entryO, entryN]; entryN.typeOfPntr # lineNum OR entryO.typeOfPntr # lineNum OR entryN.otherIndex # indexO OR entryO.otherIndex # indexN => EXIT; ENDCASE; indexN _ indexN + 1; indexO _ indexO + 1; ENDLOOP; }; ENDLOOP; WorkingMsg['%]; }; { indexN _ totalNewLines - 1; WHILE indexN >= 0 DO entry: FileArrayEntry = newArray[indexN]; Process.CheckForAbort[]; indexN _ indexN - 1; IF entry.typeOfPntr = lineNum THEN { indexO _ entry.otherIndex - 1; WHILE indexN >= 0 AND indexO >= 0 DO entryN: FileArrayEntry = newArray[indexN]; entryO: FileArrayEntry = oldArray[indexO]; symEntry: SymbolTableEntry _ entryN.symEntry; Process.CheckForAbort[]; SELECT TRUE FROM entryN.typeOfPntr = symTable AND entryO.typeOfPntr = symTable AND symEntry = entryO.symEntry => { ConnectEntries[symEntry, indexO, indexN, entryO, entryN]; }; entryN.typeOfPntr # lineNum OR entryO.typeOfPntr # lineNum OR entryN.otherIndex # indexO OR entryO.otherIndex # indexN => EXIT; ENDCASE; indexN _ indexN - 1; indexO _ indexO - 1; ENDLOOP; }; ENDLOOP; WorkingMsg['~]; }; ENDLOOP; { CancelMatch: PROC [array1, array2: FileArray, totalNumOfLinesFile1, index: INT] = { DO entry1: FileArrayEntry _ array1[index]; IF entry1.typeOfPntr = symTable THEN EXIT; entry1.typeOfPntr _ symTable; array2[entry1.otherIndex].typeOfPntr _ symTable; index _ index + 1; IF ((index >= totalNumOfLinesFile1) OR (entry1.otherIndex # array1[index - 1].otherIndex + 1)) THEN EXIT; ENDLOOP; }; IF switchLinesForMatch > 1 THEN { indexN _ 0; DO oldIndexN: INT _ indexN; indexN _ indexN + 1; Process.CheckForAbort[]; IF indexN >= totalNewLines THEN EXIT; IF newArray[indexN].typeOfPntr = lineNum THEN { WHILE ((indexN < totalNewLines) AND (newArray[indexN].otherIndex = newArray[indexN-1].otherIndex + 1)) DO indexN _ indexN + 1; ENDLOOP; IF (indexN - oldIndexN) < switchLinesForMatch AND indexN < totalNewLines THEN CancelMatch[newArray, oldArray, totalNewLines, oldIndexN]; }; ENDLOOP; }; WorkingMsg['&]; { LeadingNumber: PROC [char: CHAR, number: INT] = { leadingZeroes: INTEGER _ columns - 1; tempIndex: INT _ number; IF switchMergeFiles THEN RETURN; Process.CheckForAbort[]; difFile.PutF["%g/", [character[char]]]; DO IF tempIndex < 10 THEN EXIT; tempIndex _ tempIndex/10; leadingZeroes _ leadingZeroes - 1; ENDLOOP; THROUGH [0..leadingZeroes) DO difFile.PutChar['0]; ENDLOOP; difFile.Put[[integer[number]]]; difFile.PutRope[") "]; }; PrintDelta: PROC [file: REF, which: CHAR, entry: FileArrayEntry] = { st: STREAM = NARROW[file]; pos: INT = entry.instance.first.pos; LeadingNumber[which, pos]; IO.SetIndex[st, pos]; THROUGH [0..entry.len) DO c: CHAR _ IO.GetChar[st ! IO.EndOfStream => EXIT]; IO.PutChar[difFile, c]; ENDLOOP; IO.PutChar[difFile, '\n]; }; PrintCedarDelta: PROC [file: REF, index, start, total: INT, array: FileArray] RETURNS [INT] = { st: STREAM = NARROW[file]; IF start < total THEN { leadChar: CHAR _ IF file = oldFile THEN '1 ELSE '2; lastChar: CHAR _ 0C; lastIndex: INT _ MIN[index+1, total] - 1; lastEntry: FileArrayEntry = array[lastIndex]; pos: INT _ array[start].instance.first.pos; end: INT _ lastEntry.instance.first.pos+lastEntry.instance.first.len; WHILE pos > 0 DO IO.SetIndex[st, pos - 1]; lastChar _ IO.GetChar[st]; IF IsEndOfLine[lastChar] THEN EXIT; pos _ pos - 1; ENDLOOP; LeadingNumber[leadChar, pos]; IO.SetIndex[st, pos]; DO lastChar _ IO.GetChar[st ! IO.EndOfStream => EXIT]; IF IsEndOfLine[lastChar] THEN { IF pos >= end THEN EXIT; IO.PutChar[difFile, '\n]; LeadingNumber[leadChar, pos]; } ELSE IO.PutChar[difFile, lastChar]; pos _ pos + 1; ENDLOOP; IO.PutChar[difFile, '\n]; WHILE index < total DO IF array[index].instance.first.pos >= end THEN EXIT; index _ index + 1; ENDLOOP; }; RETURN [index]; }; DumpOutDiffAndMoveAhead: PROC = { IF NOT anyDifferencesSeen THEN { OpenDifFileAndWriteHeader[]; difFile.PutF["%g%g\n", [rope[Asterisks]], [rope[Asterisks]]]; }; SELECT TRUE FROM (indexN >= totalNewLines) OR (indexO >= totalOldLines) => { indexN _ totalNewLines; indexO _ totalOldLines; }; newArray[indexN].typeOfPntr = lineNum => indexO _ newArray[indexN].otherIndex ENDCASE => indexN _ oldArray[indexO].otherIndex; SELECT pData FROM $Cedar => { indexO _ PrintCedarDelta[oldFile, indexO, startDifO, totalOldLines, oldArray]; difFile.PutF["%g\n", [rope[Asterisks]]]; indexN _ PrintCedarDelta[newFile, indexN, startDifN, totalNewLines, newArray]; }; ENDCASE => { IF switchMergeFiles THEN CopySpan[oldArray, startDifO, indexO-1, oldFile, old, totalOldLines] ELSE { FOR index: INT IN [startDifO..indexO) DO entry: FileArrayEntry = oldArray[index]; PrintDelta[oldFile, '1, entry]; ENDLOOP; FOR index: INT IN [indexO..indexO + switchLinesForContext) WHILE (index < totalOldLines) DO entry: FileArrayEntry = oldArray[index]; PrintDelta[oldFile, '1, entry]; ENDLOOP; }; indexO _ indexO + switchLinesForContext; difFile.PutF["%g\n", [rope[Asterisks]]]; IF switchMergeFiles THEN CopySpan[newArray, startDifN, indexN-1, newFile, new, totalNewLines] ELSE { FOR index: INT IN [startDifN..indexN) DO entry: FileArrayEntry = newArray[index]; PrintDelta[newFile, '2, entry]; ENDLOOP; FOR index: INT IN [indexN..indexN + switchLinesForContext) WHILE (index < totalNewLines) DO entry: FileArrayEntry = newArray[index]; PrintDelta[newFile, '2, entry]; ENDLOOP; }; indexN _ indexN + switchLinesForContext; }; difFile.PutF["\n%g%g\n", [rope[Asterisks]], [rope[Asterisks]]]; IF switchMergeFiles THEN CopySpan[newArray, indexN-switchLinesForContext, indexN-1, newFile, both, totalNewLines]; startDifN _ indexN; WHILE indexN < totalNewLines AND newArray[indexN].typeOfPntr # symTable DO IF newArray[indexN].otherIndex # newArray[indexN - 1].otherIndex + 1 THEN EXIT; indexN _ indexN + 1; indexO _ indexO + 1; ENDLOOP; IF switchMergeFiles AND indexN>startDifN THEN CopySpan[newArray, startDifN, indexN-1, newFile, both, totalNewLines]; startDifN _ indexN; startDifO _ indexO; }; TryToResolveConflicts: PROC [array1, array2: FileArray, index1, index2: INT] RETURNS [okToDumpDiff: BOOL] = { entry1: FileArrayEntry _ array1[index1]; lastRange1: INT _ index1 + entry1.otherIndex - index2; FOR tempIndex: INT IN [index2..entry1.otherIndex) DO entry2: FileArrayEntry _ array2[tempIndex]; IF entry2.typeOfPntr = lineNum THEN { IF entry2.otherIndex > lastRange1 THEN CancelMatch[array2, array1, totalOldLines, tempIndex] ELSE { CancelMatch[array1, array2, totalNewLines, index1]; RETURN[FALSE]; }; }; ENDLOOP; RETURN [TRUE]; }; CopySpan: PROC [array: FileArray, index1, index2: INT, in: REF, lineType: LineType _ both, limit: INT_-1] = { inNode: Node = NARROW[in]; nesting: INT; IF limit>=0 THEN { IF index1 >= limit THEN RETURN; index2 _ MIN[index2, limit-1]; }; IF index1>index2 THEN RETURN; nesting _ TextNode.Level[array[index1].node] - TextNode.Level[difFileNode.node]; WHILE nesting > 1 DO []_EditSpan.Copy[difFileNode.root, fillerNode.root, TextNode.MakeNodeLoc[difFileNode.node], TextNode.MakeNodeSpan[fillerNode.node, fillerNode.node], after, 1]; nesting _ nesting - 1; ENDLOOP; []_EditSpan.Copy[difFileNode.root, inNode.root, TextNode.MakeNodeLoc[difFileNode.node], TextNode.MakeNodeSpan[array[index1].node, array[index2].node], after, nesting]; IF lineType=both THEN difFileNode.node _ TextNode.LastWithin[difFileNode.root] ELSE { node: TextNode.Ref; WHILE (node_TextNode.StepForward[difFileNode.node])#NIL DO len: INT = Rope.Length[TextNode.NodeRope[node]]; difFileNode.node _ node; SELECT lineType FROM old => TiogaFileOps.AddLooks[FR[node], 0, len, 'y]; new => TiogaFileOps.AddLooks[FR[node], 0, len, 'z]; ENDCASE; ENDLOOP; }; }; startDifN: INT; startDifO: INT; dumpDiff: BOOL; columns: NAT _ 1; max: INT _ MAX[posInNewFile, posInOldFile]; DO IF max < 10 THEN EXIT; max _ max/10; columns _ columns + 1; ENDLOOP; indexN _ 0; indexO _ 0; IF switchMergeFiles THEN OpenDifFileAndWriteHeader[]; DO IF indexN >= totalNewLines OR indexO >= totalOldLines THEN EXIT ELSE { entryN: FileArrayEntry _ newArray[indexN]; entryO: FileArrayEntry _ oldArray[indexO]; IF entryN.typeOfPntr # lineNum THEN EXIT; IF entryO.typeOfPntr # lineNum THEN EXIT; IF entryN.otherIndex # indexO THEN EXIT; IF entryO.otherIndex # indexN THEN EXIT; indexN _ indexN + 1; indexO _ indexO + 1; }; ENDLOOP; IF switchMergeFiles AND indexN>0 THEN CopySpan[newArray, 0, indexN-1, newFile, both]; startDifN _ indexN; startDifO _ indexO; dumpDiff _ FALSE; WHILE ((indexN < totalNewLines) AND (indexO < totalOldLines)) DO entryN: FileArrayEntry = newArray[indexN]; entryO: FileArrayEntry = oldArray[indexO]; IF entryN.typeOfPntr = lineNum OR entryO.typeOfPntr = lineNum THEN { IF entryN.typeOfPntr = lineNum AND entryO.typeOfPntr = lineNum THEN { IF entryN.otherIndex = indexO AND entryO.otherIndex = indexN THEN GOTO dumpoutthedifference; IF (entryN.otherIndex - indexO) > (entryO.otherIndex - indexN) THEN CancelMatch[newArray, oldArray, totalNewLines, indexN] ELSE CancelMatch[oldArray, newArray, totalOldLines, indexO]; }; IF entryN.typeOfPntr = lineNum THEN dumpDiff _ TryToResolveConflicts[newArray, oldArray, indexN, indexO] ELSE dumpDiff _ TryToResolveConflicts[oldArray, newArray, indexO, indexN]; EXITS dumpoutthedifference => dumpDiff _ TRUE; }; IF dumpDiff THEN { DumpOutDiffAndMoveAhead[]; dumpDiff _ FALSE; } ELSE { indexN _ indexN + 1; indexO _ indexO + 1; }; ENDLOOP; IF startDifN < totalNewLines OR startDifO < totalOldLines THEN DumpOutDiffAndMoveAhead[]; WorkingMsg['*]; IF switchMergeFiles THEN TiogaFileOps.Store[FR[difFileNode.root], difFileName]; }; IF anyDifferencesSeen THEN FinishUp[Rope.Cat[IF switchMergeFiles THEN "merged version written on file " ELSE " differences written on file ", difFileName, ".\n"]] ELSE {FinishUp[" no differences encountered.\n"]; result _ $NoAction}; IF ~switchMergeFiles THEN { IO.Close[NARROW[oldFile]]; IO.Close[NARROW[newFile]]; } }; EXITS usageError => {msg _ "Usage error: Waterlily file1 file2\n"; result _ $Failure}; fatalError => {result _ $Failure}; }; ShortName: PROC [name: ROPE] RETURNS [ROPE] = { bang: INT _ Rope.Length[name]; pos: INT _ bang; WHILE (pos _ pos - 1) > 0 DO SELECT Rope.Fetch[name, pos] FROM '>, '/, '] => {pos _ pos + 1; EXIT}; '!, '. => bang _ pos; ENDCASE; ENDLOOP; RETURN [Rope.Flatten[name, pos, bang - pos]]; }; DefaultExtension: PROC [name: ROPE, ext: ROPE, forceExt: BOOL] RETURNS [ROPE] = { len: INT _ Rope.Length[name]; pos: INT _ len; WHILE (pos _ pos - 1) > 0 DO SELECT Rope.Fetch[name, pos] FROM '>, '/, '] => EXIT; '., '! => RETURN [name]; ENDCASE; ENDLOOP; IF forceExt THEN RETURN[Rope.Concat[name, ext]]; [] _ FS.FileInfo[name ! FS.Error => GOTO NoFile]; RETURN [name]; -- if file exists, don't change its name EXITS NoFile => RETURN[Rope.Concat[name, ext]]; }; TR: PROC[ref: REF] RETURNS [TextNode.Ref] = TRUSTED INLINE { RETURN[LOOPHOLE[ref]]; }; FR: PROC[ref: REF] RETURNS [TiogaFileOps.Ref] = TRUSTED INLINE { RETURN[LOOPHOLE[ref]]; }; NewNode: PROC RETURNS [node: Node] = { node _ NEW[NodeBody _ [TR[TiogaFileOps.CreateRoot[]]]]; node.node _ node.root; NodeProps.PutProp[n: NARROW[node.root, TextNode.Ref], name: $NewlineDelimiter, value: Rope.Flatten["\n"]]; }; NodeFromFile: PROC[fileName: ROPE] RETURNS [node: Node] = { node _ NEW[NodeBody _ []]; node.root _ PutGet.FromFile[fileName]; node.node _ node.root; }; IsEndOfLine: PROC [c: CHAR] RETURNS [BOOL] = INLINE { RETURN [c = '\n OR c = 015C OR c = 012C]; }; Commander.Register[key: "Waterlily", proc: WaterlilyProc, doc: LongHelpMsgW, clientData: NIL]; Commander.Register[key: "Cedarlily", proc: WaterlilyProc, doc: LongHelpMsgC, clientData: $Cedar]; Commander.Register[key: "Tigerlily", proc: WaterlilyProc, doc: LongHelpMsgM, clientData: $Merge]; Commander.Register[key: "MergeLily", proc: WaterlilyProc, doc: LongHelpMsgM, clientData: $Merge]; -- The old name }. Waterlily.mesa Copyright Ó 1984, 1985, 1988, 1991 by Xerox Corporation. All rights reserved. Swinehart, November 18, 1985 2:35:32 pm PST Russ Atkinson (RRA) December 17, 1991 7:43 pm PST Last tweaked by Mike Spreitzer on October 17, 1988 4:48:07 pm PDT Bill Jackson (bj) November 17, 1988 5:14:01 pm PST Jules Bloomenthal August 5, 1991 12:21 pm PDT Michael Plass, February 21, 1991 9:56 am PST Willie-s, February 17, 1992 12:51 pm PST Part of this algorithm cribbed from Heckel, Paul. A Technique For Isolating Differences Between Files. Comm. ACM 21,4 (April 1978), 264-268. Pointer to which courtesy of Ed Taft. Make this greater to experiment with multiple phases of match finding Turn this on to get different characters for different phases of the process. PROC [cmd: Handle] RETURNS [result: REF _ NIL, msg: ROPE _ NIL]; these switches are global or local. these switches are global only. We need a new buffer We are at the end of the stream. If the token is empty, then raise EndOfStream. Special processing for Cedar tokens Now do a little canonicalization to avoid reporting meaningless differences. Semicolons are quite common, but not very important, and are often optional. So we can safely ignore them. This may just be the end of the interesting part of the file. This may just be the end of the interesting part of the file. This is an interesting little hack. It tends to improve token uniqueness by appending the peek character, tends to reduce the number of tokens in the table (by swallowing lots of single-character tokens), and thereby improves matching. Character code finesse Character code finesse We only get here when we are using full lines as tokens. Here we process the token to make it canonical start here. Process arguments Switches specified here The old file name is really the dif file name Pass 1 & 2 Pass 1 In Pass 1 we scan the new file (the second one mentioned in the command line) for lines (or tokens), and enter them into the symbol table. Pass 2 Pass 2 is like Pass1, except that we are scanning the old file (the first one mentioned in the command line). Pass 3 In Pass 3 we transform all of the instances into file array entries. [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL] Pass 4 In Pass 4 we run through the symbol table to connect all lines (or tokens) that appear only once in both files (OR appear once with a given peek char). Those lines (or tokens) are the places where the files are known to coincide. [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL] Pass 5 In Pass 5 we extend matching entries outwards by scanning forwards. Pass 6 In Pass 6 we extend matching entries outwards by scanning backwards. Passes 7 and 8 Pass 7 In Pass 7 we cancel matches that don't extend far enough. This is to prevent excessive context switching in reporting differences. Pass 8 In Pass 8 we actually print the differences, skipping over the matches. must be a better way to do this. Dump out the line indicated by the entry Dump out the difference indicated, extending the difference through the start of the line containing the first token, and through the end of the line containing the last token. Return the index after the last token on the last line printed. First, get to the preceding line start by scanning backwards Now, put out lines until the rem count is exhausted Now skip over tokens we inadvertently covered during our printing to the end of line. The index returned is the one after the one we printed. If merging, print the context lines here. Move ahead to get beyond the last line from the old file. Node Management Ê(ý˜headšœ™IcodešœN™NL™+L™1L™AL™2L™-L™,L™(L˜Lšœµ™µL™šÏk ˜ Lšœ œ˜Lšœ œ˜(Lšœ œ!˜3Lšœ œ˜Lšœ œ˜&LšœœD˜LLšœœ¼œ ˜×Lšœ œ ˜Lšœœ˜Lšœœ˜$LšœœG˜TLšœœBœ˜RLšœœ@˜LLšœ œL˜ZLšœ œD˜V——šœ œ˜Lšœ:œœO˜–L˜Lšœœœ˜Lšœœœœ˜L˜Lšœœœ˜1šœœœ˜#LšœÏc˜+Lšœž˜+Lšœœž˜)Lšœ˜L˜—Lšœœœ ˜)šœ œœ˜Lšœœž˜$Lšœœž5˜?Lšœœž+˜CLšœœž˜%Lšœœž'˜2L˜—L˜Lšœ œœ˜#Lš œœœ œœœ˜KL˜Lšœœœ˜-šœœœ˜"Lšœ˜Lšœ˜Lšœ œ˜Lšœœ˜L˜ Lšœœ˜L˜—Lšœœ˜Lšœœœ ˜Lš œ œœ œ œ˜8L˜šœœ˜Lšœÿ˜ÿ—šœœ˜Lšœ½˜½—šœœ˜Lšœ’˜’L˜—šœ œ˜LšœE™E—šœ œœ˜LšœM™M——šœ(˜(Lš œœ œœœœ™@L˜Lšœœœ˜L˜Lšœ˜Lšœ˜Lšœœ ˜šœœ˜%L˜—Lšœœ˜Lšœœ˜L˜Lšœœ˜Lšœœ˜Lšœ œ˜L˜Lšœ œž˜#Lšœ œž˜#Lšœ œ˜Lšœœ˜L˜Lšœ œœ˜Lšœ œœ˜Lšœ œœ˜L˜Lšœ œ,˜;Lšœœ˜L˜Lšœ#™#Lšœ œ˜(L˜7Lšœ>œœ˜JLšœœœ˜Lšœœœ˜Lšœœœ˜!Lšœœœ˜'L˜Lšœ™Lšœœ˜Lšœœ˜L˜Lšœœœ˜!Lšœœ˜ Lšœœ˜ L˜Lšœ œ˜"Lšœ œ˜#L˜šÏnœœœ/œœœœ˜{Lšœ œ˜$Lšœœ;˜Tšœ$œ˜3Lšœ'˜'šœ˜ šœœ˜)Lšœ œ œ ˜'—Lšœ2˜2L˜——šœ ˜šœ˜Lšœ ˜ Lšœ˜Lšœ˜—šœ˜Lšœ ˜ Lšœ˜Lšœ˜—Lšœœ˜—L˜L˜—šŸ œœœœ˜QLš œœœœœ˜ Lšœœœ ˜0Lšœ˜š˜Lšœ˜L˜Lšœœœœ˜Lšœœœ˜Lšœ œ"˜/šœœ˜Lšœ2˜2˜Lšœ/˜/Lš œœœœœ˜L˜Lšœœœœ˜!L˜—Lšœ œ,˜@—šœ˜L˜——Lšœ ™ L˜Lšœ9œ˜?L˜Lšœœ œ˜JLšœœ˜6Lšœœ+œ˜XLšœ-œœœ˜=L˜Lšœ œ˜ Lšœœ˜ L˜LšÏb™šœ˜šœ:˜:Lšœ1œœ ˜BL˜L˜—Lšœ œ˜Lšœ œœ˜Lšœ"˜"Lšœœœ˜šœœœœ˜LL˜—šœœœ˜Lšœœ ˜Lšœœœ˜šœœ˜Lšœ™Lšœœ˜Lšœœ˜šœœœ ˜Lšœœ˜šœ˜ Lšœœ˜L˜"L˜"Lšœ#˜#Lšœ#˜#Lšœ@˜@˜ L˜Lšœœœ˜'L˜—Lšœ+œ˜3Lšœ œ œ˜;Lšœ œ œ ˜=Lšœœ˜Lšœ˜—L˜ Lšœ˜—Lšœ˜L˜—šœœ˜Lšœ-™-Lšœœœœ ˜'Lšœ˜Lšœ˜Lšœ˜L˜—šœ ˜˜Lšœ˜Lšœ$˜$Lšœ1˜1Lšœ1˜1Lšœœœ˜7Lšœ˜—˜Lšœ˜Lšœ$˜$Lšœ1˜1Lšœ1˜1Lšœ˜—Lšœœœ ˜—Lšœ˜—Lšœœœœ ˜'L˜L˜šœ˜šœœ ˜Lšœœ˜2Lšœœ ˜Lšœ˜—LšœN˜NLšœN˜NL˜—Lšœ˜Lšœ˜—L˜Lš  ™ šœ˜š ™L™Š—Lšœ œœ˜Lšœœ˜Lšœœ˜ L˜ Lšœ˜Lšœ˜š˜Lšœœ˜ Lšœœ˜ šœu˜uLšœœ˜—LšœP˜PL˜"Lšœ˜—Lšœœœ ˜)Lšœ œ˜,Lšœ˜L˜š ™L™m—L˜ Lšœ˜Lšœ˜š˜Lšœœ˜ Lšœœ˜ šœu˜uLšœœ˜—LšœP˜PL˜"Lšœ˜—Lšœœœ ˜)Lšœ œ˜,Lšœ˜L˜š ™LšœD™D—šœ˜•StartOfExpansion; -- [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL]šŸœ˜Lšœ#œœ™7Lšœ œ˜,Lšœ,˜,Lšœ,˜,šœ)œœ˜?šœœ˜5Lšœ˜Lšœ˜Lšœ˜L˜Lšœ˜Lšœ˜—Lšœ˜—šœ)œœ˜?šœœ˜5Lšœ˜Lšœ˜Lšœ˜L˜Lšœ˜Lšœ˜—Lšœ˜—Lšœœ˜Lšœ˜—Lšœ%˜%Lšœ˜Lšœ˜—L˜šœ˜Lšœ>˜>Lšœ˜L˜—Lšœ˜L˜—šœ˜L˜š ™L–; -- [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL]šœæ™æ—šœ˜šŸœ˜Lšœ#œœ™7Lšœ œ˜,Lšœ,˜,Lšœ,˜,Lšœ˜šœœ˜Lšœ œ œ˜#šœœœ˜+Lšœ˜—šœ˜ Lšœ˜Lšœ˜LšœP˜PL˜——Lšœœ˜Lšœ˜—Lšœ%˜%Lšœ˜Lšœ˜L˜—š ™L–; -- [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL]šœC™C—˜L˜ šœ˜Lšœ)˜)Lšœ˜L˜šœœ˜$Lšœ˜šœœ˜:Lšœ*˜*Lšœ*˜*Lšœ-˜-šœœ˜šœœœ˜_Lšœ9˜9—Lš œœœœœ˜Lšœ˜—L˜L˜Lšœ˜—Lšœ˜—Lšœ˜—Lšœ˜L˜—L˜š ™L–; -- [key: SymTab.Key, val: SymTab.Val] RETURNS [quit: BOOL]šœD™D—˜L˜šœ ˜Lšœ)˜)Lšœ˜L˜šœœ˜$Lšœ˜šœ œ ˜$Lšœ*˜*Lšœ*˜*Lšœ-˜-Lšœ˜šœœ˜šœœœ ˜aLšœ9˜9Lšœ˜—šœœœœ˜yLšœ˜—Lšœ˜—L˜L˜Lšœ˜—Lšœ˜—Lšœ˜—Lšœ˜L˜L˜—Lšœ˜—L˜Lš ™šœ˜šŸ œœ:œ˜Sš˜Lšœ'˜'Lšœœœ˜*Lšœ˜Lšœ0˜0L˜Lšœ"œ9 œ˜iLšœ˜—šœ˜L˜——š ™L™ƒ—šœœ˜!Lšœ ˜ š˜Lšœ œ ˜L˜Lšœ˜Lšœœœ˜%šœ'œ˜/šœœD˜iLšœ˜Lšœ˜—šœ,œ˜MLšœ:˜:—Lšœ˜—Lšœ˜—Lšœ˜—Lšœ˜L˜š ™L™G—šœ˜šŸ œœœ œ˜1Lšœ ™ Lšœœ˜%Lšœ œ ˜Lšœœœ˜ Lšœ˜Lšœ'˜'š˜Lšœœœ˜L˜L˜"Lšœ˜—Lšœœœ˜;Lšœ˜L˜Lšœ˜—šŸ œœœ œ˜DLšœ(™(Lšœœœ˜Lšœœ˜$Lšœ˜Lšœ˜šœ˜Lš œœœœœ˜2Lšœ˜Lšœ˜—Lšœ˜L˜—š Ÿœœœœœœ˜_Lšœñ™ñLšœœœ˜šœœ˜Lš œ œœœœ˜3Lšœ œ˜Lšœ œœ˜)Lšœ-˜-Lšœœ#˜+Lšœœ=˜EL™<šœ ˜Lšœ˜Lšœ œ ˜Lšœœœ˜#Lšœ˜Lšœ˜—L™3Lšœ˜Lšœ˜š˜Lšœ œœœ˜3šœ˜šœ˜Lšœ œœ˜Lšœ˜Lšœ˜L˜—Lšœœ˜#—Lšœ˜Lšœ˜—Lšœ˜L˜LšœŽ™Žšœ˜Lšœ(œœ˜4L˜Lšœ˜—L˜—Lšœ ˜L˜—šŸœœ˜!šœœœ˜ Lšœ˜Lšœ=˜=Lšœ˜—šœœ˜šœœ˜;Lšœ˜L˜L˜—šœ(˜(Lšœ$˜$—šœ˜ Lšœ%˜%——šœ˜˜ LšœN˜NLšœ(˜(LšœN˜NL˜—šœ˜ šœ˜LšœE˜Išœ˜šœœœ˜(Lšœ(˜(Lšœ˜Lšœ˜—š œœœ*œ˜[Lšœ(˜(Lšœ˜Lšœ˜—L˜——Lšœ(˜(Lšœ(˜(šœ˜LšœE˜Išœ˜šœœœ˜(Lšœ(˜(Lšœ˜Lšœ˜—š œœœ*œ˜[Lšœ(˜(Lšœ˜Lšœ˜—L˜——Lšœ(˜(L˜—L˜—Lšœ?˜?L˜L™)šœ˜LšœY˜YL˜—Lšœ9™9L˜šœœ'˜JLšœCœœ˜OLšœ˜Lšœ˜Lšœ˜—L˜šœœ˜-LšœF˜F—L˜L˜Lšœ˜—š Ÿœœ-œœœ˜mLšœ(˜(Lšœ œ'˜6šœ œœ˜4Lšœ+˜+šœœ˜%šœ˜!Lšœ6˜:šœ˜Lšœ3˜3Lšœœ˜Lšœ˜——Lšœ˜—Lšœ˜—Lšœœ˜Lšœ˜—š Ÿœœ$œœ$œ˜mLšœœ˜Lšœ œ˜ Lš œ œœœœ œ˜TLšœœœ˜LšœP˜Pšœ ˜L˜ŸL˜Lšœ˜—L˜§šœ˜Lšœ9˜=šœ˜L˜šœ/œ˜:Lšœœ(˜0L˜šœ ˜Lšœœ˜4Lšœœ˜3Lšœ˜—Lšœ˜—L˜——Lšœ˜—Lšœ œ˜Lšœ œ˜Lšœ œ˜Lšœ œ˜Lšœœœ˜+š˜Lšœ œœ˜L˜ L˜Lšœ˜—L˜ L˜ Lšœœ˜5š˜šœœ˜5Lšœ˜ šœ˜Lšœ*˜*Lšœ*˜*Lšœœœ˜)Lšœœœ˜)Lšœœœ˜(Lšœœœ˜(L˜L˜L˜——Lšœ˜—šœœ ˜%Lšœ/˜/L˜—L˜L˜Lšœ œ˜šœœ˜@Lšœ*˜*Lšœ*˜*šœœœ˜Dšœœœ˜ELšœœœœ˜\šœ<˜>Lšœ7˜;Lšœ8˜<—Lšœ˜—šœ˜LšœE˜ILšœF˜J—Lšœ$œ˜.Lšœ˜—šœ ˜ šœ˜Lšœ˜Lšœ œ˜Lšœ˜—šœ˜Lšœ˜L˜Lšœ˜——Lšœ˜—šœœ˜>Lšœ˜—Lšœ˜Lšœœœ!˜OLšœ˜——˜šœ˜Lšœœœ#œ6˜ŒLšœB˜FL˜—šœœ˜Lšœœ ˜Lšœœ ˜L˜—Lšœ˜—L˜š˜LšœP˜PLšœ"˜"—L˜Lšœ˜L˜—š Ÿ œœœœœ˜/Lšœœ˜Lšœœ˜šœ˜šœ˜!Lšœœ˜$L˜Lšœ˜—Lšœ˜—Lšœ'˜-L˜L˜—šŸœœœœ œœœ˜QLšœœ˜Lšœœ˜šœ˜šœ˜!Lšœœ˜Lšœ œ˜Lšœ˜—Lšœ˜—Jšœ œœ˜0Jšœœœ œ ˜1Lšœž)˜7Jšœ œ˜/L˜L˜—L˜™L™š Ðknœœœœœ˜