-- File: WalnutUpdateImpl.mesa
-- Contents:
-- reads the logStream, starting at startPos, & makes the appropriate database updates

-- Created by: Willie-Sue on April 27, 1983
-- Last edited by:
-- Willie-Sue on December 5, 1983 11:24 am

DIRECTORY
DB USING [Value,
    DestroyEntity, Eq, GetF, GetName, GetP, GetPList, Null, SetP,
    I2V, V2B, V2E, V2I, V2S],
FS USING [StreamOpen],
IO,
 Rope,
 RopeIO USING [GetRope],
 WalnutControlPrivate USING [InternalConfirm],
 WalnutDB USING [Msg, MsgSet,
     deletedMsgSet, mCategoryIs, mHasBeenReadIs, mHeadersPos, mMsgLengthIs,
     msNumInSetIs, mPrefixPos, mSubjectIs,
     AddMsgToMsgSet, DeclareMsg, DeclareMsgSet, DestroyMsgSet, MsgRecToMsg,
     RemoveMsgFromMsgSet, SetMsgHasBeenRead],
 WalnutDBLog USING [walnutInfoRelship, wStartExpungePos],
 WalnutVoice USING [CheckForWalnuthatch, RemoveInterestEntry],
 WalnutLog USING [minPrefixLength, MsgRec, MessageRecObject,
     copyBuffer, msgIDRope,
     ConstructMsgID, GenerateNewMsgID],
 WalnutRetrieve USING [ParseMsgIntoFields],
 WalnutStream USING [FindStartOfEntry, IsStart, MakeLogEntry, MsgRecFromStream,
     TagAndValue],
 WalnutWindow USING [walnutLogName, Report, ReportRope];

WalnutUpdateImpl: CEDAR PROGRAM

IMPORTS DB, FS, IO, Rope, RopeIO,
 WalnutControlPrivate, WalnutDB, WalnutDBLog, WalnutLog,
 WalnutRetrieve, WalnutStream, WalnutVoice, WalnutWindow

EXPORTS WalnutStream =

BEGIN OPEN DB, WalnutDB, WalnutLog, WalnutStream;

ROPE: TYPE = Rope.ROPE;

skipRope: ROPE← "Unexpected EOF; trying for next entry";
maxTailRewriteBytes: INT← 1250000;  -- try this out

BadCopyForExpunge: SIGNAL[numRead, numExpected: INT] = CODE;

-- ********************************************************
UpdateFromStream: PUBLIC PROC [strm: IO.STREAM, startPos: INT] RETURNS[success: BOOL] =
BEGIN
doReport: BOOL← (startPos = 0);  -- report if scavenging from beginning
BadFormat: PROC[s: ROPE] =
{ IF doReport THEN
  WalnutWindow.Report[IO.PutFR
   ["Bad log file format at %g: %g", IO.int[strm.GetIndex[]], IO.rope[s]]]
};

BEGIN ENABLE IO.EndOfStream => {BadFormat["Unexpected EOF"]; GOTO GiveUp};
entryLength, prefixLength, beginMsgPos: INT;
msg: Msg;
msgSet: MsgSet;
entryChar: CHAR;
count: INT← 0;

DomainUpdate: PROC RETURNS[BOOL] =
BEGIN
  msName, tag: ROPE;
  [tag, msName]← TagAndValue[strm, 2];
IF NOT tag.Equal["name"] THEN {BadFormat["expected name"]; RETURN[FALSE]};
  WalnutWindow.ReportRope[Rope.FromChar[entryChar]];
SELECT entryChar FROM
'- =>
{msgSet← DeclareMsgSet[msName, OldOnly].msgSet;
IF msgSet = NIL THEN RETURN[TRUE];
[]← DestroyMsgSet[msgSet]
};
'+ => []← DeclareMsgSet[msName];
ENDCASE => ERROR;
RETURN[TRUE];
END;

RelationUpdate: PROC RETURNS[BOOL] =
BEGIN
mName, categoryName, tag: ROPE;
[tag, mName]← TagAndValue[strm, 2];
IF NOT tag.Equal["of"] THEN {BadFormat["of?"]; RETURN[FALSE]};
msg← DeclareMsg[mName, OldOnly].msg;
IF msg=NIL THEN {BadFormat[Rope.Cat[mName, " doesn\'t exist!"]]; RETURN[FALSE]};
[tag, categoryName]← TagAndValue[strm, 2];
IF NOT tag.Equal["is"] THEN {BadFormat["is?"]; RETURN[FALSE]};
WalnutWindow.ReportRope[Rope.FromChar[entryChar]];
SELECT entryChar FROM
'- =>
{ msgSet← DeclareMsgSet[categoryName, OldOnly].msgSet; -- check if msgSet exists
IF msgSet # NIL THEN []← RemoveMsgFromMsgSet[msg, msgSet]
};
'+ => -- create msgSet if it doesn't exist
 []← AddMsgToMsgSet[msg, DeclareMsgSet[categoryName].msgSet]
ENDCASE => ERROR;
RETURN[TRUE];
END;

ProcessHasBeenRead
: PROC =
BEGIN
  len: INT;
  mName: ROPE← RopeIO.GetRope[strm, prefixLength-minPrefixLength ! IO.EndOfStream =>
  { WalnutWindow.Report["\nUnexpected EOF, ignoring HasBeenRead entry"]; GOTO eof}];
IF mName.Fetch[len← mName.Length[]-1] = '\n THEN mName← mName.Substr[0, len];
  msg← DeclareMsg[mName, OldOnly].msg;
IF msg = NIL THEN RETURN; -- ignore
  SetMsgHasBeenRead[msg];

EXITS eof => RETURN;
END;

strm.SetIndex[startPos];
DO
-- Read *start* from log
[beginMsgPos, prefixLength, entryLength, entryChar]← FindStartOfEntry[strm, doReport];
IF entryLength = -1 THEN RETURN[TRUE];
IF (entryLength=0) OR (entryLength=prefixLength) AND
NOT (entryChar = '←) THEN RETURN[TRUE];
-- Do delete, create, or message update to database
SELECT entryChar FROM
'← => ProcessHasBeenRead[]; -- mark message as read

'+, '- => -- add or remove relship
BEGIN
foo, domainOrRelation: ROPE;
ok: BOOL;
strm.SetIndex[beginMsgPos+prefixLength];  -- ignore prefix info
[domainOrRelation, foo] ← TagAndValue[strm, 2];

IF domainOrRelation.Equal["Domain"] THEN
{ IF (ok← foo.Equal["MsgSet"]) THEN ok← DomainUpdate[] -- Add or delete MsgSet
ELSE BadFormat[IO.PutFR["%g is not a valid domain", IO.rope[foo]]];
}
ELSE IF domainOrRelation.Equal["Relation"] THEN
{ IF (ok← foo.Equal["mCategory"]) THEN ok← RelationUpdate[] --AddTo or RemoveFrom
ELSE BadFormat["expected mCategory"]
}
   ELSE -- domainOrRelation not "Domain" or "Relation"
{BadFormat["not domain or relation"]; ok← FALSE};

IF ~ok THEN strm.SetIndex[beginMsgPos+entryLength] -- next entry
ELSE IF strm.GetChar[]#'\n THEN BadFormat["Missing CR"];-- Skip over the trailing CR
END;

ENDCASE => -- regular message entry
BEGIN
msgRec: MsgRec←
 WalnutStream.MsgRecFromStream[strm, prefixLength, entryLength-prefixLength];
IF msgRec = NIL THEN
WalnutWindow.Report[
IO.PutFR["\n Bad Entry at %g; skipping to next entry", IO.int[beginMsgPos]]]
ELSE
{ IF entryChar # '? THEN msgRec.hasBeenRead← TRUE;
  []← MsgRecToMsg[msgRec];
  count← count + 1;
IF doReport THEN
  {IF count MOD 10 = 0 THEN
 WalnutWindow.ReportRope[IF count MOD 100 = 0 THEN "!" ELSE "~"]}
ELSE WalnutWindow.ReportRope["."];
};
strm.SetIndex[beginMsgPos+entryLength];
END;
ENDLOOP;

EXITS GiveUp => RETURN[TRUE];  -- try to press on with what we have
END;
END;

ExpungeFromStream: PUBLIC PROC[strm, tempLog: IO.STREAM, doUpdates, tailRewrite: BOOL]
  RETURNS[startExpungePos: INT, ok: BOOL] =
-- Dumping is driven from the log file & preserves the bits that came from Grapevine
-- Dumps all the Msgs in the database to a tempLog, setting all
-- their body pointers to reference the NEW log, then copies tempLog to logStream
BEGIN OPEN IO;
newLen: INT;
BEGIN ENABLE IO.EndOfStream => GOTO badLogFile;
msg: Msg;

toBeDestroyedList: LIST OF Msg;
count: INT← 0;
expungeFilePos, startPos, prefixLength, entryLength: INT;
entryChar: CHAR;
numBad: INTEGER← 0;
DoCount: PROC =
{IF (count← count + 1) MOD 10 = 0 THEN
 WalnutWindow.ReportRope[IF count MOD 100 = 0 THEN "!" ELSE "~"]
};
WriteBadLogEntry: PROC[startPos: INT] RETURNS[nextStartPos: INT] =
 { errorStream: STREAM← FS.StreamOpen["WalnutExpunge.errlog",
   IF (numBad← numBad+1) = 1 THEN $create ELSE $append];
  line: ROPE;
  strm.SetIndex[startPos];
  errorStream.PutRope["\n******************************************************"];
  errorStream.PutRope[
   IO.PutFR["\nBad entry from pos %g of log file, written at %g\n", int[startPos], time[]]];
  errorStream.PutRope[strm.GetLineRope[]]; -- *start* line
  errorStream.PutChar['\n];
  DO
  nextStartPos← strm.GetIndex[];
  line← strm.GetLineRope[];
IF IsStart[line].startFound THEN {nextStartPos← strm.GetIndex[]-8; EXIT};
  errorStream.PutRope[line];
  errorStream.PutChar['\n];
ENDLOOP;
  errorStream.SetLength[errorStream.GetIndex[]];
  errorStream.Close[];
};
CopyEntryIfNecessary: PROC =
 { thisTag, thisValue: ROPE← NIL;
  thisMsg: Msg;
  doCopy: BOOLTRUE;
  prefixPos: INT;
  IF entryChar = '← THEN  -- hasbeenread entry
   { -- strm.SetIndex[startPos+minPrefixLength]; where strm is pos'd
   thisValue← RopeIO.GetRope[strm, prefixLength-minPrefixLength-1];
   []← strm.GetChar[ ! IO.EndOfStream => CONTINUE]
   }
   ELSE
  { strm.SetIndex[startPos+prefixLength];
   [thisTag, thisValue]← TagAndValue[strm, 2];
   IF thisTag.Equal["Relation"] AND thisValue.Equal["mCategory"] THEN
   { [thisTag, thisValue]← TagAndValue[strm, 2];
   IF ~thisTag.Equal["of"] THEN thisValue← NIL;
   };
   };
  IF thisValue # NIL THEN
   { thisMsg← DeclareMsg[thisValue, OldOnly].msg;
   IF ~Null[thisMsg] THEN
   IF (prefixPos← V2I[GetP[thisMsg, mPrefixPos]]) >= startExpungePos THEN
     doCopy← FALSE;
   };
  IF doCopy THEN
   { numToDo: INT;
   strm.SetIndex[startPos];
FOR numToDo← entryLength, numToDo-512 UNTIL numToDo<512 DO
[]← strm.GetBlock[copyBuffer];
tempLog.PutBlock[copyBuffer];
ENDLOOP;
IF numToDo # 0 THEN
{ numRead: INT← strm.GetBlock[copyBuffer, 0, numToDo];
IF numRead # numToDo THEN SIGNAL BadCopyForExpunge[numRead, numToDo];
tempLog.PutBlock[copyBuffer, 0, numToDo];
copyBuffer.length← 512;
};
   };
 };

bytesInTail: INT;
logIsOnAlpine: BOOL← WalnutWindow.walnutLogName.Find[".alpine]", 0, FALSE] > 0;
tempLog.SetIndex[0];
startExpungePos←
IF tailRewrite THEN
V2I[GetF[WalnutDBLog.walnutInfoRelship, WalnutDBLog.wStartExpungePos]] ELSE 0;

-- if log file is on alpine AND tailRewrite AND startExpungePos#0 AND
-- (loglength-startExpungePos)>1.25mb, THEN do full expunge anyway (and inform user)
IF logIsOnAlpine AND tailRewrite AND startExpungePos#0 AND
  (bytesInTail← strm.GetLength[] - startExpungePos) > maxTailRewriteBytes THEN
  { WalnutWindow.Report[IO.PutFR[
    "Tail of log to be expunged was %g bytes - doing full expunge", IO.int[bytesInTail]]];
  tailRewrite← FALSE;
  startExpungePos← 0;
  };

strm.SetIndex[startExpungePos];
IF startExpungePos = 0 THEN tailRewrite← FALSE;

DO   -- loop for dumping messages & making other log entries
msgID: ROPENIL;
fullText: ROPENIL;
headersPos, curPos: INT;
badEntry: BOOLFALSE;

[startPos, prefixLength, entryLength, entryChar]← FindStartOfEntry[strm, TRUE];
IF entryLength = 0 THEN EXIT;
IF (entryChar # ' ) AND (entryChar # '?) THEN-- perhaps copy other entry to tempLog
{ IF startExpungePos # 0 THEN CopyEntryIfNecessary[];
strm.SetIndex[startPos+entryLength]; -- for good measure, even after CopyEntry
LOOP
};

headersPos← startPos+prefixLength;
UNTIL (curPos← strm.GetIndex[]) = headersPos DO
-- look for a msgID: field
  tag, value: ROPE;

[tag, value]← TagAndValue[strm: strm, inc: 2];
IF Rope.Equal[tag, msgIDRope, FALSE] THEN msgID← value;
IF curPos > headersPos THEN -- bad entry we don't understand
 { nextStartPos: INT← WriteBadLogEntry[startPos];
  cMsg: ROPE← " Confirm to push on, deny to stop the Expunge";
WalnutWindow.ReportRope[PutFR["\nBad message entry at log pos %g;", int[startPos]]];
  WalnutWindow.Report[" entry written on WalnutExpunge.errlog"];
  WalnutWindow.Report[cMsg];
IF (ok← WalnutControlPrivate.InternalConfirm[])
    THEN {strm.SetIndex[nextStartPos]; badEntry← TRUE; EXIT};
RETURN[startExpungePos, FALSE]};
ENDLOOP;
IF badEntry THEN LOOP;

IF msgID = NIL THEN
BEGIN  -- have to read fullText to fashion msgID
mr: MsgRec← NEW[MessageRecObject];
[]← WalnutRetrieve.ParseMsgIntoFields[mr, strm, entryLength-prefixLength !
IO.EndOfStream =>
  {WalnutWindow.Report[skipRope]; strm.SetIndex[startPos+entryLength]; LOOP}];
mr.gvID← ConstructMsgID[mr];
mr.msgLength← entryLength-prefixLength;
-- need to make sure this is really a unique id for this message
-- some msgs from old mail files are not
IF ~CheckID[mr] THEN {strm.SetIndex[startPos+entryLength]; LOOP};
 strm.SetIndex[startPos+prefixLength];  -- back up stream
 msgID← mr.gvID;
END;

msg← DeclareMsg[msgID, OldOnly].msg;
IF (msg=NIL) OR Null[msg] THEN {strm.SetIndex[startPos+entryLength]; LOOP}
ELSE
BEGIN
curPrefixPos, thisPrefixLen, thisEntryLen: INT;
thisMsgSet: MsgSet;
nameOfCatsList: ROPENIL;

-- if is only in deletedMsgSet, don't put on tempLog
FOR mL: LIST OF DB.Value← GetPList[msg, mCategoryIs], mL.rest UNTIL mL=NIL DO
IF ~Eq[thisMsgSet← V2E[mL.first], deletedMsgSet] THEN
  nameOfCatsList← Rope.Cat[nameOfCatsList, " ", DB.GetName[thisMsgSet]];
ENDLOOP;

IF nameOfCatsList.Length[] = 0 THEN
  { toBeDestroyedList← CONS[msg, toBeDestroyedList]; GOTO doneWithOne};
  msgID← Rope.Cat[msgID, "\nCategories:", nameOfCatsList];

IF fullText = NIL THEN fullText←
RopeIO.GetRope[strm, entryLength-prefixLength ! IO.EndOfStream =>
{ WalnutWindow.Report[skipRope]; GOTO doneWithOne}];

DoCount[];
[expungeFilePos, thisPrefixLen, thisEntryLen]← MakeLogEntry[
   tempLog,
IF V2B[GetP[msg, mHasBeenReadIs]] THEN message ELSE newMessage,
 fullText, Rope.Cat[msgIDRope, ": ", msgID, "\n"]];

-- set header & body pos pointers to posn in NEW log if doing updates:
IF doUpdates THEN
  { thisPrefixPos: INT← startExpungePos + expungeFilePos - thisEntryLen;
  curHeadersPos: INT← V2I[GetP[msg, mHeadersPos]];
  thisHeadersPos: INT← thisPrefixPos+thisPrefixLen;
  curPrefixPos← V2I[GetP[msg, mPrefixPos]];
  IF (curPrefixPos # thisPrefixPos) THEN []← SetP[msg, mPrefixPos, I2V[thisPrefixPos]];
  IF (curHeadersPos # thisHeadersPos) THEN
   []← SetP[msg, mHeadersPos, I2V[thisHeadersPos]];
  };


EXITS
  doneWithOne => strm.SetIndex[startPos+entryLength];
END;  -- put message on log file
ENDLOOP;  -- loop for dumping messages

WalnutWindow.Report[PutFR["\nDumped %g messages from Log File... ", int[count]]];
tempLog.SetLength[newLen← tempLog.GetIndex[]];
tempLog.Flush[];  -- make sure tempLog is in good shape
WalnutWindow.Report[PutFR["Old log length was %g bytes", int[strm.GetLength[]]]];
IF tailRewrite THEN
{ WalnutWindow.Report[PutFR
  ["Previous end of log was %g bytes", int[strm.GetLength[]-startExpungePos]]];
WalnutWindow.Report[PutFR
  ["New end of log file is %g bytes (%g messages)", int[newLen], int[count]]];
WalnutWindow.Report[PutFR["New log length is %g bytes", int[startExpungePos+newLen]]];
}
ELSE
WalnutWindow.Report[PutFR
  ["New log length is %g bytes (%g messages)", int[newLen], int[count]]];

IF doUpdates THEN
 { nuh: REF ANY;
  msg: Msg;
  id: ROPE;
  WalnutWindow.ReportRope[" Destroying Msgs in Deleted MsgSet ..."];

-- may see a msg more than once in the log file, hence must check if already destroyed
  count← 0;
  nuh← WalnutVoice.CheckForWalnuthatch[];
FOR mL: LIST OF Msg← toBeDestroyedList, mL.rest UNTIL mL = NIL DO
  IF ~Null[msg← mL.first] THEN
   { IF nuh#NIL THEN id← GetName[msg];
   DestroyEntity[mL.first];  -- destroy the message first
   IF nuh#NIL THEN WalnutVoice.RemoveInterestEntry[NIL, id];
   DoCount[];
   };
ENDLOOP;
  WalnutWindow.Report[PutFR["\n%g Msgs destroyed",int[count]]];
BEGIN   -- fix up num in deleted (should be 0 but who knows)
  num: INT← V2I[GetP[deletedMsgSet, msNumInSetIs]] - count;
  []← SetP[deletedMsgSet, msNumInSetIs, I2V[num]];
END;
};  -- end doUpdates

RETURN[startExpungePos, TRUE];

EXITS
badLogFile =>
{ tempLog.SetLength[tempLog.GetIndex[]];
tempLog.Close[];
RETURN[startExpungePos, FALSE]
};
END;
END;

CheckID: PROC[mr: MsgRec] RETURNS[useThisMsg: BOOL] =
BEGIN
 len: INT;
 subj: ROPE;
 msg: Msg;
DO
  msg← DeclareMsg[mr.gvID, OldOnly].msg;
IF (msg=NIL) OR Null[msg] THEN RETURN[FALSE];
  len← V2I[GetP[msg, mMsgLengthIs]];
IF len # mr.msgLength THEN { GenerateNewMsgID[mr]; LOOP};
  subj← V2S[GetP[msg, mSubjectIs]];
IF ~Rope.Equal[subj, mr.subject] THEN { GenerateNewMsgID[mr]; LOOP};
RETURN[TRUE];
ENDLOOP;
END;

END.