-- file: CodeCompare.mesa 
-- Edited by: Loretta, 24-Feb-81 18:45:50  
-- Edited by: Satterthwaite, March 21, 1983 1:00 pm  
  
DIRECTORY
  Ascii: TYPE USING [CR, ESC, NUL, SP], 
  Environment: TYPE USING [bytesPerWord, wordsPerPage], 
  Exec: TYPE USING [AddCommand, commandLine, w],
  BcdDefs: TYPE USING [Base, BCD, MTRecord, VersionStamp], 
  BcdOps: TYPE USING [BcdBase, MTHandle, SGHandle],
  FileStream: TYPE USING [InvalidHandle], 
  Format: TYPE USING [NumberFormat], 
  Runtime: TYPE USING [CallDebugger, GetBcdTime], 
  Stream: TYPE USING [Delete, EndOfStream, Handle, GetBlock],
  Streams: TYPE USING [Destroy], 
  String: TYPE USING [AppendChar, AppendString, EquivalentString, StringToDecimal], 
  Storage: TYPE USING [FreeString], 
  LongStorage: TYPE USING [Words, FreeWords], 
  STP: TYPE USING [
    Close, Create, CreateFileStream, CreateRemoteStream, Destroy, Error, ErrorCode,
    FileErrors, Handle, Login, NextFileName, Open, SetDirectory],   
  Time: TYPE USING [Append, Unpack],
  TTY: TYPE USING [
    GetChar, GetID, PutChar, PutCR, PutDecimal, PutLine, PutNumber, PutString,
    ResetUserAbort, UserAbort], 
  UserCredentialsUnsafe: TYPE USING [GetUserCredentials, SetUserCredentials];
      
CodeCompare: PROGRAM
  IMPORTS
    Exec, FileStream, LongStorage, Runtime, Storage, STP,
    Stream, Streams, String, Time, TTY, UserCredentialsUnsafe = {
  
  bytesPerWord: CARDINAL = Environment.bytesPerWord;
  wordsPerPage: CARDINAL = Environment.wordsPerPage;
  bytesPerPage: CARDINAL = bytesPerWord*wordsPerPage;

  format: Format.NumberFormat = [base~8,zerofill~FALSE,unsigned~TRUE,columns~8];
  byteformat: Format.NumberFormat = [base~8,zerofill~FALSE,unsigned~TRUE,columns~3];
  pair: TYPE = RECORD[left, right: [0..0FFh]];

  STPuser: STP.Handle ← NIL;
  name: STRING ← [80];
  localName: STRING ← [40];
  switches: STRING ← [5];
  version, sourceVersion: BcdDefs.VersionStamp;
  tmpString: STRING = [25];
  differences:  BOOL ← FALSE;
  MaxDiffs: CARDINAL ← 20;
  difcount: CARDINAL;
  BufSize: CARDINAL = 20*wordsPerPage;
  buffer1: LONG POINTER;
  buffer2: LONG POINTER;
  header: BcdOps.BcdBase;

-- Utilities

  CompareStreams: PROC [stream1, stream2: Stream.Handle, length1, length2: CARDINAL] = {
    bufcount1, bufcount2: CARDINAL ← 0;
    code1, code2: LONG POINTER TO ARRAY [0..BufSize) OF WORD;

    BuffersFilled: PROC [f1, f2: Stream.Handle, l1, l2: CARDINAL] RETURNS [BOOL] = {
      IF MIN[l1,l2] <= 0 THEN RETURN [FALSE];
      SELECT bufcount1 FROM
       = bufcount2 => {
	  code1 ← buffer1;
	  code2 ← buffer2;
	  [bufcount1,,] ← f1.GetBlock[
	    block~[blockPointer~buffer1, startIndex~0, stopIndexPlusOne~l1*bytesPerWord]]; 
	  [bufcount2,,] ← f2.GetBlock[
	    block~[blockPointer~buffer2, startIndex~0, stopIndexPlusOne~l2*bytesPerWord]];
	  bufcount1 ← bufcount1/bytesPerWord;
	  bufcount2 ← bufcount2/bytesPerWord;
	  RETURN [MIN[bufcount1, bufcount2] > 0]};
       > bufcount2 => {
	  code1 ← buffer1;
	  code2 ← code2+bufcount1; --change array origin
	  bufcount2 ← bufcount2 - bufcount1;
	  [bufcount1,,] ← f1.GetBlock[
	    block~[blockPointer~buffer1, startIndex~0, stopIndexPlusOne~l1*bytesPerWord]]; 
	  bufcount1 ← bufcount1/bytesPerWord;
	  RETURN [bufcount1 > 0]};
       < bufcount2 => {
	  code1 ← code1+bufcount2; --change array origin
	  code2 ← buffer2;
	  bufcount1 ← bufcount1 - bufcount2;
	  [bufcount2,,] ← f2.GetBlock[
	    block~[blockPointer~buffer2, startIndex~0, stopIndexPlusOne~l2*bytesPerWord]]; 
	  bufcount2 ← bufcount2/bytesPerWord;
	  RETURN [bufcount2 > 0]};
       ENDCASE;
      RETURN [FALSE]};

  -- body of CompareStreams

    difcount ← 0;
    WHILE BuffersFilled[stream1,stream2,length1,length2] DO
      length1 ← length1 - bufcount1; length2 ← length2 - bufcount2;
      FOR i: CARDINAL IN [0..MIN[bufcount1, bufcount2]) DO
        IF code1[i] # code2[i] THEN {
          w: pair;
          (Exec.w).PutNumber[i, format];
          (Exec.w).PutNumber[code1[i], format];
          (Exec.w).PutChar['[]; 
          w ← LOOPHOLE[code1[i], pair];
          (Exec.w).PutNumber[w.left, byteformat];
          (Exec.w).PutChar[',]; (Exec.w).PutNumber[w.right, byteformat];
          (Exec.w).PutChar[']];
          (Exec.w).PutNumber[code2[i],format];
          (Exec.w).PutChar['[];
          w ← LOOPHOLE[code2[i], pair];
          (Exec.w).PutNumber[w.left, byteformat];
          (Exec.w).PutChar[',]; (Exec.w).PutNumber[w.right, byteformat];
          (Exec.w).PutChar[']];
          (Exec.w).PutCR;
          IF difcount = MaxDiffs THEN { 
            (Exec.w).PutLine["Too many differences encountered. Quitting."L];
	    GOTO quit};
          difcount ← difcount + 1; differences ← TRUE};
        ENDLOOP;
	REPEAT quit => NULL;
      ENDLOOP;

    IF difcount = MaxDiffs THEN (Exec.w).PutString["More than "L];
    (Exec.w).PutDecimal[difcount];
    (Exec.w).PutLine[" differences"L]};

  Config: SIGNAL = CODE;
  NoCode: SIGNAL = CODE;

  FindCode: PROC [stream: Stream.Handle, buf: LONG POINTER] RETURNS [
    codeCount: CARDINAL, dateStamp, sourceStamp: BcdDefs.VersionStamp] = {
    -- positions stream to start of code
    -- FindCode returns size in words (codeCount)
    OPEN BcdDefs;
    ENABLE
      UNWIND => {NULL};
    streamPos: CARDINAL;
    sgPointer: BcdDefs.Base;
    mtPos, sgPos: CARDINAL;
    codeBase: CARDINAL;
    mOffset: CARDINAL;
    mth: BcdOps.MTHandle;
    sgh: BcdOps.SGHandle;

    AdvanceStream: PROC [newPos: CARDINAL] = {
      -- positions stream to byte position newPos
      incr: CARDINAL;
      WHILE newPos > streamPos DO
	[incr,,] ← stream.GetBlock[block~[buf, 0, MIN[BufSize, newPos - streamPos]]];
        streamPos ← streamPos + incr;
   	ENDLOOP};

    [streamPos,,] ← stream.GetBlock[block~[header,0,BCD.SIZE*bytesPerWord]]; --read header
    -- get module table, which contains index of code segment, 
    -- starting offset in segment (in words) 
    -- and length of code (in bytes)
    IF header.nConfigs > 0 THEN SIGNAL Config;
    mtPos ← header.mtOffset*bytesPerWord;
    sgPos ← header.sgOffset*bytesPerWord;
    dateStamp ← header.version;
    sourceStamp ← header.sourceVersion;
    IF mtPos < sgPos THEN { 
     -- read module table first, record fields, then overwrite with segment table
      AdvanceStream[mtPos];
      mth ← LOOPHOLE[buf, BcdOps.MTHandle];
      AdvanceStream[mtPos + LOOPHOLE[header.mtLimit,CARDINAL]*bytesPerWord];
      mOffset ← mth.code.offset;
      codeCount ← mth.code.length;
      sgPos ← sgPos + LOOPHOLE[mth.code.sgi,CARDINAL]*bytesPerWord;
      AdvanceStream[sgPos];
      sgh ← LOOPHOLE[buf, BcdOps.SGHandle];
      AdvanceStream[sgPos + LOOPHOLE[header.sgLimit,CARDINAL]*bytesPerWord]}
    ELSE { 
     -- must read segment table before module table, but don't know which part of 
     --segment table! store segment table in first part of buffer, advance buffer 
     -- pointer to read module table behind it, access both at once
      AdvanceStream[sgPos];
      sgPointer ← LOOPHOLE[buf,BcdDefs.Base];
      AdvanceStream[sgPos + LOOPHOLE[header.sgLimit,CARDINAL]*bytesPerWord];
      buf ← LOOPHOLE[LOOPHOLE[buf,LONG CARDINAL] +
	     	LOOPHOLE[header.sgLimit,CARDINAL],LONG POINTER];
      AdvanceStream[mtPos];
      mth ← LOOPHOLE[buf, BcdOps.MTHandle];
      AdvanceStream[mtPos + LOOPHOLE[header.mtLimit,CARDINAL]*bytesPerWord];
      sgh ← @sgPointer[mth.code.sgi];
      mOffset ← mth.code.offset;
      codeCount ← mth.code.length};
    IF codeCount = 0 THEN SIGNAL NoCode;
  -- compute starting address of code (StreamPosition)
    codeBase ← (sgh.base-1)*bytesPerPage + mOffset*bytesPerWord;
    AdvanceStream[codeBase];
  -- round codeCount up to nearest work boundary and convert to word count
    IF codeCount MOD 2 # 0 THEN codeCount ← codeCount + 1;
    codeCount ← codeCount/bytesPerWord;
    RETURN};

  ExhaustStream: PROC [stream: Stream.Handle, buf: LONG POINTER] = {
    DO
      ENABLE Stream.EndOfStream => {EXIT};
      [,,] ← stream.GetBlock[block~[buf, 0, BufSize*bytesPerWord]];
      ENDLOOP};

  CheckStream: PROC [stream: Stream.Handle] = {
    ENABLE
      UNWIND => {Streams.Destroy[stream 
                 ! FileStream.InvalidHandle => {stream.Delete; CONTINUE}]};
    remoteFileName: STRING ← NIL;
    remoteFileName ← STP.NextFileName[stream];
    IF remoteFileName # NIL THEN Storage.FreeString[remoteFileName]
    ELSE SIGNAL STP.Error[noSuchFile,"File not Found."L]};

  ForceBCDExtension: PROC [string: STRING] = {
    FOR i: CARDINAL IN [0..name.length) DO
      IF name[i] = '. THEN {string.length ← i; EXIT};
      ENDLOOP;
    String.AppendString[string, ".bcd"L]};

  InitSTP: PROC [server: STRING] = {
    herald: STRING ← NIL;
    userName: STRING = [40];
    userPassword: STRING = [40];
    STPuser ← STP.Create[];
    herald ← STP.Open[STPuser,server !
      STP.Error => {
        SELECT code FROM
          noSuchHost => (Exec.w).PutLine["No such Host."L];
          connectionTimedOut => (Exec.w).PutLine["Timeout."L];
          connectionRejected => (Exec.w).PutLine["Rejected."L];
          ENDCASE => (Exec.w).PutLine["Other (unspecified) error."L]}];
    (Exec.w).PutLine[herald];
    Storage.FreeString[herald];
    UserCredentialsUnsafe.GetUserCredentials[userName, userPassword];
    STP.Login[STPuser, userName, userPassword ! STP.Error => {CONTINUE}]};

  PrintVersion: PROC [stamp: BcdDefs.VersionStamp] = {
    stampWords: CARDINAL = BcdDefs.VersionStamp.SIZE;
    str: PACKED ARRAY [0..4*stampWords) OF [0..16) = LOOPHOLE[stamp];
    digit: STRING = "0123456789abcdef"L;
    FOR i: CARDINAL IN [0..4*stampWords) DO
      (Exec.w).PutChar[digit[str[i]]] ENDLOOP};

  ProcessSwitches: PROC = {
    s: STRING = [10];
    FOR i: CARDINAL IN [0..switches.length) DO
      SELECT switches[i] FROM
        'd,'D =>
	  IF name.length = 0 THEN Runtime.CallDebugger["Called from Code Compare"L]
	  ELSE {
	    (Exec.w).PutString["\nDirectory "L];
	    (Exec.w).PutLine[name];
	    STP.SetDirectory[STPuser,name]};
        'c,'C =>
	    IF String.EquivalentString[name,"debug"] THEN 
	      Runtime.CallDebugger["Called from Code Compare"L]
	    ELSE IF String.EquivalentString[name,"dir"L] THEN 
	       IF GetToken[name,s] THEN {
		 (Exec.w).PutString["\nDirectory "L]; (Exec.w).PutLine[name];
		 STP.SetDirectory[STPuser,name]};
        'm,'M => MaxDiffs ← String.StringToDecimal[name];
        ENDCASE;
      ENDLOOP};

  TrimFileName: PROC [string: STRING] = {
    IF string[0] = '< THEN {
      i: CARDINAL ← string.length - 1;
      WHILE i > 0 DO
	IF string[i] = '> THEN {
	  i ← i+1;
	  FOR j: CARDINAL IN [i..string.length) DO 
	    string[j-i] ← string[j] ENDLOOP;
	  string.length ← string.length-i;
	  RETURN};
	i ← i - 1;
	ENDLOOP;
      string.length ← 0}};

  Login: PROC = {
    OPEN Ascii;
    user: STRING = [40];
    password: STRING = [40];
    userName: STRING = [40];
    c: CHAR;
    UserCredentialsUnsafe.GetUserCredentials[userName, NIL];
    (Exec.w).PutString["UserName: "L];
    (Exec.w).PutString[userName];
    c ← (Exec.w).GetChar;
    IF c#CR AND c#SP AND c#ESC THEN CollectRestOfNewString[user, c]
    ELSE String.AppendString[user, userName];
    (Exec.w).PutString[",  Password: "L];
    UNTIL (c←(Exec.w).GetChar)=CR OR c=SP OR c=ESC DO
      (Exec.w).PutChar['*];
      String.AppendChar[password,c];
      ENDLOOP;
    (Exec.w).PutCR;
    UserCredentialsUnsafe.SetUserCredentials[user,password];
    STP.Login[STPuser,user,password]};

  CollectRestOfNewString: PROC [s: STRING, c: CHAR] = {
    rest: STRING = [40];
    (Exec.w).PutChar[c];
    (Exec.w).GetID[rest];
    s.length ← 0;
    String.AppendChar[s, c]; String.AppendString[s, rest]};
  
  GetToken: PROC [token, switches: STRING] RETURNS [BOOL] = {
    s: STRING;
    c: CHAR;

    Get: PROC RETURNS [char: CHAR] = { 
      OPEN line ~~ Exec.commandLine;
      IF line.i >= line.s.length THEN RETURN [Ascii.NUL];
      char ← line.s.text[line.i]; line.i ← line.i.SUCC;
      RETURN};

    token.length ← switches.length ← 0;
    s ← token;
    WHILE (c ← Get[]) # Ascii.NUL DO
      SELECT c FROM
	Ascii.SP, Ascii.CR => IF s.length # 0 THEN RETURN [TRUE];
	'/ => s ← switches;
	ENDCASE => String.AppendChar[s, c];
      ENDLOOP;
    RETURN [FALSE]};
    
  DoCompare: PROC = {
    oldStream,newStream: Stream.Handle ← NIL;
    oldSize, newSize: CARDINAL;
    
    buffer1 ← LongStorage.Words[BufSize];
    buffer2 ← LongStorage.Words[BufSize];
    header ← LongStorage.Words[BcdDefs.BCD.SIZE];
    [] ← GetToken[name,switches];  -- host
    InitSTP[name];
    WHILE GetToken[name,switches] DO
      BEGIN     
      ENABLE {
	UNWIND => {
	  LongStorage.FreeWords[buffer1]; --give buffers back 
	  LongStorage.FreeWords[buffer2];
	  LongStorage.FreeWords[header];
	  STP.Close[STPuser ! STP.Error => {CONTINUE}];
	  STPuser ← STP.Destroy[STPuser]};
	STP.Error => {
          SELECT code FROM
            illegalUserName, illegalUserPassword => {
              (Exec.w).PutLine["Incorrect user/password."L];
              Login[];
              RETRY};
            ENDCASE => {(Exec.w).PutString["Error: "L]; WriteError[error]};
          LOOP};
	Config => {
	  (Exec.w).PutLine["Bound configuration; not a module."L];
	  ExhaustStream[newStream, buffer2]; 
	  newStream.Delete; 
	  Streams.Destroy[oldStream]; 
	  LOOP};
	NoCode => {
	  (Exec.w).PutLine["No code!"L];
	  ExhaustStream[newStream, buffer2]; 
	  newStream.Delete; 
	  Streams.Destroy[oldStream]; 
	  LOOP}};
      IF TTY.UserAbort[] THEN {(Exec.w).PutLine[" ...aborted."L]; TTY.ResetUserAbort[]; EXIT};
      IF switches.length > 0 THEN ProcessSwitches[]
      ELSE {
        (Exec.w).PutCR;
        ForceBCDExtension[name];
        (Exec.w).PutString["Comparing file: "L];
        (Exec.w).PutString[name];
        (Exec.w).PutString["..."L];
	localName.length ← 0;
	String.AppendString[localName, name];
	TrimFileName[localName];
	oldStream ← STP.CreateFileStream[localName, read 
	              ! STP.Error => {
		          IF code IN STP.FileErrors THEN {
			    (Exec.w).PutLine["No local file."L]; LOOP}}];
        newStream ← STP.CreateRemoteStream[STPuser, name, read 
	              ! STP.Error => {
		          Streams.Destroy[oldStream];
			  IF code IN STP.FileErrors THEN {
			    (Exec.w).PutLine["No remote file."L]; LOOP}}];
        (Exec.w).PutCR;
	CheckStream[newStream ! STP.Error => {Streams.Destroy[oldStream]}];

	  BEGIN
          ENABLE
	    STP.Error => {
              (Exec.w).PutString["Error on local file: "L];
              WriteError[error];
              ExhaustStream[newStream, buffer2];
              newStream.Delete; 
              Streams.Destroy[oldStream]; 
              LOOP};
          [oldSize,version, sourceVersion] ← FindCode[oldStream, buffer1];
          (Exec.w).PutString["Local:  "L];  PrintVersion[version];
          (Exec.w).PutString[" (from "L]; 
          tmpString.length ← 0;
          Time.Append[tmpString,Time.Unpack[[sourceVersion.time]]]; 
          (Exec.w).PutString[tmpString];
          (Exec.w).PutString[", "];
          (Exec.w).PutDecimal[oldSize]; (Exec.w).PutString[" words)\n"];
	  END;
    
	  BEGIN
          ENABLE
	    STP.Error => {
              (Exec.w).PutString["Error on remote file: "L];
              WriteError[error];
              ExhaustStream[newStream, buffer2];
              newStream.Delete;
	      Streams.Destroy[oldStream]; 
              LOOP};
          [newSize,version, sourceVersion] ← FindCode[newStream, buffer2];
          (Exec.w).PutString["Remote: "L];  PrintVersion[version];
          (Exec.w).PutString[" (from "L];
          tmpString.length ← 0;
          Time.Append[tmpString,Time.Unpack[[sourceVersion.time]]]; 
          (Exec.w).PutString[tmpString];
          (Exec.w).PutString[", "];
          (Exec.w).PutDecimal[newSize]; (Exec.w).PutString[" words)\n"];
	  END;

        CompareStreams[oldStream,newStream,oldSize,newSize 
			! STP.Error => {CONTINUE}];
    
        Streams.Destroy[oldStream];
        ExhaustStream[newStream, buffer2];
        newStream.Delete};
      END;
      ENDLOOP;

    LongStorage.FreeWords[buffer1]; --give buffers back 
    LongStorage.FreeWords[buffer2];
    LongStorage.FreeWords[header];
    STP.Close[STPuser ! STP.Error => {CONTINUE}];
    STPuser ← STP.Destroy[STPuser]};

  WriteError: PROC [s: STRING] = {
    differences ← TRUE; (Exec.w).PutLine[s]};
  
  CompareIt: PROC = {
    herald: STRING ← [60];
    String.AppendString[herald, "Cedar 4.0 Code Compare of "L];
    Time.Append[herald, Time.Unpack[Runtime.GetBcdTime[]]];
    herald.length ← herald.length - 3;
    (Exec.w).PutLine[herald]; (Exec.w).PutCR;
    differences ← FALSE;
    DoCompare[ ! STP.Error => {differences ← TRUE; CONTINUE}];
    (Exec.w).PutCR;
    IF differences THEN {
      (Exec.w).PutString["Differences or problems noted. Type any character to exit."L];
      [] ← (Exec.w).GetChar}
    ELSE (Exec.w).PutString["No differences detected."L]};
      
  Init: PROC = {Exec.AddCommand["CodeCompare.~"L, CompareIt]};

  Init[];
  
  }.