-- File: PressListener.mesa: Routines for getting for a file at a printing server.
-- GetBits is called by Press.mesa
-- Last Edited: January 10, 1983 5:10 PM By: GWilliams
-- Make it more like the TFS Streams stuff.
DIRECTORY
AltoDefs USING [BytesPerWord, PageSize],
AltoRam USING [CantFindFile, FileLooksCrufty],
EFTPDefs USING [EFTPAbortReceiving, EFTPAlreadyReceiving, EFTPEndReceiving, EFTPFinishReceiving, EFTPGetBlock, EFTPNotReceiving, EFTPOpenForReceiving, EFTPTimeOut, EFTPTroubleReceiving],
IODefs USING[CR, SP, ReadLine, WriteChar, WriteDecimal, WriteOctal, WriteLine, WriteString],
InlineDefs USING [BITOR, BITSHIFT, LongCOPY],--LongCOPY[from, nwords, to]
MesaBands USING [BandDevice, ShowBands, ShowBandsInit],
MiscDefs USING[CallDebugger, Zero],
PressDefs USING [PageG, PressPassword, RamBoot, uCodeLoaded],
PressNetDefs USING [--attributesCode,-- EndReason, --imageCode,-- PageAttributes],
PressBandsDefs USING [CloseBandsFile, OpenPressBands, InitTfsBandsBuffer, ReleaseTfsBandsBuffer],
PupDefs USING [GetPupAddress, PupPackageDestroy, PupPackageMake],
PupStream USING [AppendPupAddress],
PupTypes USING[PupAddress, PupSocketID],
SegmentDefs USING[DataSegmentHandle, DefaultBase, DeleteDataSegment, NewDataSegment, Read, SegmentAddress],
StreamDefs USING[NewWordStream, DiskHandle, FileNameError, ReadBlock],--for local mode only
TridentDefs USING [BadErrorRtn, dcReadLD, dcReadLnD, dcWriteD, dcWriteLnD, ddMgrPtr, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, eofDA, fillInDA, FA, FP, LD, NoopTfsCleanupRtn, PAGE, TfsActOnPages, TfsCloseDisk, TfsCreateDDmgr, TfsDeletePages, tfsdskPtr, TfsInit, TfsOpenFile, TFSwordsPerPage, TfsWritePages];
PressNetListener: PROGRAM
IMPORTS AltoRam, EFTPDefs, IODefs, InlineDefs, MesaBands, MiscDefs, PressDefs, PressBandsDefs, PupDefs, PupStream, SegmentDefs, StreamDefs, TridentDefs
EXPORTS PressBandsDefs, PressNetDefs =
BEGIN OPEN AltoDefs, AltoRam, EFTPDefs, IODefs, InlineDefs, MiscDefs, PressDefs, PressBandsDefs, PressNetDefs, PupDefs, PupStream, PupTypes, SegmentDefs, StreamDefs, TridentDefs;
TerminationReason: TYPE = {errorTermination, fileDoneTermination, pageDoneTermination, nullTerminationReason};
--Interpress Stuff
HeraldStart: CARDINAL = 125252B;
--Press Stuff
pressFile: BOOLEAN;
bandWidth: CARDINAL = 16;
FirstPage: TYPE = MACHINE DEPENDENT RECORD
[nPages: CARDINAL ← 1,
pageGSize: CARDINAL ← SIZE[PageG], --14B
printerMode: CARDINAL,--3=portrait, 8=Landscape
password: CARDINAL ← PressPassword,
pageGs: ARRAY[0..85) OF PageG--enough to fit into a Trident Page
];
scanSeg: DataSegmentHandle ← NIL;
scanLength: CARDINAL;
wordAddrInTfsBuffer: CARDINAL;
scanInBand: CARDINAL;
--
net stuff
connectionOpen: BOOLEAN ← FALSE;
gotAJob: BOOLEAN ← FALSE;
hostAddress: PupAddress;
pupPtr: POINTER TO PupAddress ← @hostAddress;
senderAddress: PupAddress;
shortFile, pupPkgExtant: BOOLEAN ← FALSE;
--Local Operation stuff
inFile: DiskHandle;

--Tfs stuff
TfsMaxWords: TYPE = [0..TFSwordsPerPage];
TfsCharsPerPage: CARDINAL = TFSwordsPerPage*BytesPerWord;
TfsMaxChars: TYPE = [0..TfsCharsPerPage];
pressStr: STRING = "TridentTemp.press.";
bandStr: STRING = "PBand.0.";
bitsStr: STRING = "Press.bits.";
lastPageChars: TfsMaxChars;
extendedFile: BOOLEAN;--TRUE=> we had hit EOF in adding pages
bandDiskBuffer: POINTER;
ddMgr: PUBLIC ddMgrPtr ← NIL;
disk: tfsdskPtr ← NIL;
bufferWordLen: CARDINAL = TFSwordsPerPage;
bufferByteLen: CARDINAL = BytesPerWord*bufferWordLen;
pagesLength: CARDINAL = 6;--prev, this, next, [next+1, next+2 (for adding pages)]
leaderVda, firstVda: CARDINAL ← 0;--allways holds page 0 &1 of the file
fp: FP;--fp gets filled in by TfsOpenFile
filePtr: POINTER TO FP ← @fp;
tfsSeg: DataSegmentHandle ← NIL;
tfsBuff: POINTER TO ARRAY[0..TFSwordsPerPage) OF CARDINAL;
pages: ARRAY[0..pagesLength) OF PAGE;
dAsLength: CARDINAL;
dAsBase: POINTER;--this is modified after ea call on TfsActOnPages.
pageNum: CARDINAL;
OutputFile: TYPE = {bitsFile, anyOtherFile};
outputFile: OutputFile;

--Debugging Switches
fileLengthReport: BOOLEAN ← TRUE;--print out length of received file in pages
dasMonitor: BOOLEAN ← FALSE;--for debugging tfs file handler.
debuggerIfTfsError: PUBLIC BOOLEAN ← TRUE;
checkTermination: PUBLIC BOOLEAN ← TRUE;
localSource: BOOLEAN ← TRUE;--for debugging

--Signals & Errors
CommErr: TYPE = {alreadyHaveJob, nullComErr, endReceiving, noisyChannel, protocolError, illegalEnd, notReceiving, alreadyReceiving};
errorComm: ERROR[e: CommErr, wordsTransferred: CARDINAL ← 0, s: STRING ← NIL] = CODE;
errorTfs: PUBLIC ERROR[e: EndReason] = CODE;
EOFerror: ERROR = CODE;

GetBits: PUBLIC PROC[] RETURNS[okToProceed: BOOLEAN ← FALSE]=
--Raises no signals or errors
BEGIN
--pa: PageAttributes;
endReason: EndReason ← illegalReason;
iii: CARDINAL ← 0;--used in data fetching loop
--inCoreAddress: POINTER TO ARRAY OF WORD;
tooMuchData: BOOLEAN ← FALSE;--set when sender sends too much data
receivedFile: BOOLEAN ← FALSE;
--scanLineLength: CARDINAL;----copy of scanLength
wordsInBuff: CARDINAL;

BEGIN
extendedFile ← FALSE;--if true, add empty page to end of file on exiting.
lastPageChars ← 0;
IF ~FirstPageCheck[] THEN RETURN[FALSE];

WHILE ~receivedFile
DO
TridentThere[! errorTfs => IF e=noTrident
THEN {WriteLine["Trident not up"L]; GOTO getOut};];

GetTfsBuffer[];
BEGIN ENABLE BEGIN--for catching signals from the communications proc.
errorComm =>
{SELECT e FROM
noisyChannel => {WriteLine["Noisy Channel, aborting transfer"L];
EFTPAbortReceiving["Channel too noisy, aborting transfer"L!
EFTPNotReceiving => CONTINUE]};
endReceiving =>{WriteTfsPage[wordsTransferred];--empty the last load from the net
GOTO closeConn;}; --all OK
ENDCASE;
GOTO incompleteXFer};
errorTfs => SELECT e FROM tridentError, hitEOF, dANotFilled => {endReason ← e; GOTO done}; ENDCASE;
END;--of catch series

wordsInBuff ← GetAJob[! errorComm => IF e = alreadyReceiving THEN {PupPackageDestroy[]; GOTO getOut}];
OpenAppropriateFile[(IF pressFile THEN pressStr ELSE bandStr), filePtr
! errorTfs => {SELECT e FROM noTrident => WriteLine["Trident not up"L];
cantFindFile => {endReason ← e;
WriteString["Can’t find "L]; WriteLine[(IF pressFile THEN pressStr ELSE bandStr)];};
ENDCASE; GOTO done}--state cleaned up at exit--];

InitTfsBuffer[anyOtherFile];--find first VDA to write
--
Main data snarfing loop
--inCoreAddress ← InitScanBuffer[pa];----get enough space for a scan line; must call after InitTfsBuffer
--scanLineLength ← scanLength;----scan Length is valid now.
IF shortFile THEN {WriteTfsPage[wordsInBuff]; GOTO closeConn};--File < =1024 words.

DO
WriteTfsPage[wordsInBuff];--the first load was gotten in GetAJob
wordsInBuff ← GetBuffer[tfsBuff, TFSwordsPerPage];
ENDLOOP;

EXITS
incompleteXFer =>
{IF checkTermination THEN
CallDebugger["File transfer trouble"];
CloseStorage[];
LOOP};--restart @ WHILE ~ receivedFile
closeConn => NULL;
END;--of scope of the catch phrase

CloseStorage[];
receivedFile ← TRUE;
ENDLOOP;
okToProceed ← TRUE;

EXITS
getOut=> NULL;
done=>
{ReleaseTfsBuffer[];
CloseServerConnection[];--turn off net if on.
SELECT endReason FROM
emptyBuffReason=>WriteLine["Empty Page: error!"L];
illegalReason =>WriteLine["illegal End."L];
tridentError =>{WriteLine["Trident error"L];
EFTPAbortReceiving["Trident error"L];};
hitEOF => {WriteLine["Ran into EOF on write"L];
EFTPAbortReceiving["Trident ran into EOF on file write"L];};
dANotFilled =>{WriteLine["Trident software trouble -- bad DA multiple times"L];
EFTPAbortReceiving["Trident software trouble -- bad DA"L];};
ENDCASE;

SELECT endReason FROM
tridentError => NULL;
cantFindFile, emptyBuffReason, hitEOF, dANotFilled => {IF disk # NIL THEN disk ← TfsCloseDisk[disk, FALSE]; ddMgr ← NIL};
ENDCASE;
};
END;
IF checkTermination THEN
IF ~okToProceed THEN CallDebugger["Exiting with error from GetBits"L];
END;
--of GetBits

CloseStorage: PROC []=--Close connection, give back free storage and close the disk
{CloseServerConnection[];
CloseTfsBuffers[];
disk←TfsCloseDisk[disk, FALSE];--delete the ddMgr too
ddMgr ← NIL;
IF localSource THEN
CloseInputFile[];
};--
CloseStorage.

CloseInputFile:
PROC[]=
{
IF localSource THEN
inFile.destroy[inFile];
};

FirstPageCheck: PROC [] RETURNS[goAhead: BOOLEAN ← TRUE]=
{
IF SIZE[FirstPage] > TFSwordsPerPage THEN
{WriteLine["First page description exceeds Trident Page Length"];
RETURN[FALSE]};
};
--FirstPageCheck
GetBuffer: PROC[buffer: POINTER, len: CARDINAL] RETURNS [wordsInBufCt: CARDINAL ← 0]=
--copy from net Stream to buffer len amount of words
BEGIN
blockByteLen, bytesToGet: CARDINAL ← 0;
bufferEnd: POINTER ← buffer + len;--actually is first word past buffer
bufferPos: POINTER ← buffer;
getABuffEndReason: EndReason ← illegalReason;

BEGIN

UNTIL bufferPos = bufferEnd
DO
bytesToGet ← (bufferEnd - bufferPos) + (bufferEnd - bufferPos);--remember, bufferEnd is one past end of buffer
blockByteLen ← 0;
IF localSource
THEN--read that number of words, and convert back to bytes
{blockByteLen ← BITSHIFT[ReadBlock[inFile, bufferPos, BITSHIFT[bytesToGet, -1]], 1];
IF inFile.endof[inFile] THEN {getABuffEndReason ← doneReason; GOTO done;}}
ELSE
blockByteLen ← EFTPGetBlock[bufferPos, bytesToGet!
EFTPNotReceiving => {getABuffEndReason ← errorNotReceiving; GOTO done;};
EFTPEndReceiving => {getABuffEndReason ← doneReason; GOTO done;};
EFTPTroubleReceiving => {getABuffEndReason ← errorTroubleReceiving; GOTO done;};
EFTPTimeOut => RETRY];

bufferPos ← bufferPos + blockByteLen/2;
wordsInBufCt ← wordsInBufCt + BITSHIFT[blockByteLen, -1];--divide by bytes/word
ENDLOOP;

EXITS
done=>
{wordsInBufCt ← wordsInBufCt + BITSHIFT[blockByteLen, -1];--divide by bytes/word;

SELECT getABuffEndReason FROM
doneReason =>ERROR errorComm[endReceiving, wordsInBufCt, NIL];--not necessarily an error
errorTroubleReceiving =>ERROR errorComm[noisyChannel, wordsInBufCt, NIL];
errorNotReceiving =>ERROR errorComm[notReceiving, 0, NIL];
illegalReason =>ERROR errorComm[illegalEnd, wordsInBufCt, NIL];
ENDCASE;
};
END;
END;
--of GetBuffer

GetAJob: PUBLIC PROC[] RETURNS[wordsReturned: CARDINAL ← 0]=
--
Changed this routine. It used to get a 1-word code that specified data or attributes.
-- If the code was attributesCode, it would get the attributes and return.
-- Now it just reads in the first 1K words (or what ever is available) and checks to see whether it is an Interpress doc or a Press doc.
{filename: STRING ← [200];
typedMessage: BOOLEAN ← FALSE;
getAJobEndReason: EndReason ← illegalReason;
--code: CARDINAL;
pupAddressString: STRING ← [30];

IF localSource THEN
{--first see that there is a file on the disk
BEGIN ENABLE FileNameError => BEGIN WriteLine["Can’t find file."L]; RETRY; END;
WriteString["Filename to read: "];
ReadLine[filename]; WriteChar[CR];
[inFile] ← NewWordStream[filename, Read];--open file for testing.
END;
[wordsReturned] ← GetBuffer[tfsBuff, TFSwordsPerPage!
errorComm =>
IF e = endReceiving AND (wordsReturned ← wordsTransferred) # 0
THEN {shortFile ← TRUE; CONTINUE};
];--get first page’s bytes of file
PostJob[];
RETURN [wordsReturned];
};

IF gotAJob THEN ERROR errorComm [alreadyHaveJob, , ];
shortFile ← FALSE;
WHILE ~gotAJob DO
pupAddressString.length ← 0;
IF ~connectionOpen THEN
{IF ~pupPkgExtant THEN
{PupPackageMake[];
pupPkgExtant ← TRUE;
GetPupAddress[pupPtr, "ME"];
--don’t use the normal socket for debugging!
pupPtr.socket ← PupSocketID[1, 25B];--[0, 20B] is the normal printer socket
};--use [1, 25B] for debugging PressNetSender

senderAddress ← EFTPOpenForReceiving[pupPtr↑!
EFTPTimeOut =>
{IF ~typedMessage
THEN {WriteLine["Listening for print request."]; typedMessage ← TRUE;};
RESUME};
EFTPAlreadyReceiving =>
{WriteLine["Connection Already Open!"L];
ERROR errorComm[alreadyReceiving, 0, NIL]};
];
connectionOpen ← TRUE;
};

WriteString["Connection open to "L];
AppendPupAddress[pupAddressString, senderAddress];
WriteLine[pupAddressString];
typedMessage ← FALSE;

[wordsReturned] ← GetBuffer[tfsBuff, TFSwordsPerPage!
errorComm =>
{IF e = endReceiving AND (wordsReturned ← wordsTransferred) # 0
THEN {shortFile ← TRUE; CONTINUE}
ELSE {EFTPFinishReceiving[!
EFTPNotReceiving => CONTINUE];
connectionOpen ← FALSE; LOOP};
};
];--get first page’s bytes of file

PostJob[];--see if this is an InterPress file; if not, is a Press file
ENDLOOP;

};
--GetAJob
PostJob: PROC[]=
{IF tfsBuff[0] # HeraldStart THEN pressFile ← TRUE ELSE pressFile ← FALSE;
IF ~localSource
THEN gotAJob ← TRUE
ELSE gotAJob ← FALSE;};
GetBitsFromBands
: PUBLIC PROC[] RETURNS[okToProceed: BOOLEAN ← FALSE]=
--Raises no signals or errors
BEGIN

pa: PageAttributes;
endReason: EndReason ← illegalReason;
iii: CARDINAL ← 0;--used in data fetching loop
inCoreAddress: POINTER TO ARRAY OF WORD;
tooMuchData: BOOLEAN ← FALSE;--set when sender sends too much data
receivedFile: BOOLEAN ← FALSE;
shortFile ← FALSE;

BEGIN
--this routine destroys the ddMgr if it fails
OpenPressBits[filePtr! errorTfs => {SELECT e FROM noTrident => WriteLine["Trident not up"L];
cantFindFile => WriteLine["Can’t find Press.bits"L];
ENDCASE; GOTO getOut --no state to clean up--}];

OpenPressBands[! errorTfs => {SELECT e FROM noTrident => WriteLine["Trident not up"L];
cantFindFile =>
{WriteLine["Can’t find PBand.0"L];
disk ← TfsCloseDisk[disk, FALSE]; --get rid of Bits file disk object
ddMgr ← NIL}; --and the community ddMgr
ENDCASE; GOTO getOut}];

bandDiskBuffer ← InitTfsBandsBuffer[];--init the input buffer for Press.Bands
pa ← MesaBands.ShowBandsInit[hornet];
GetTfsBuffer[];
InitTfsBuffer[bitsFile];--init the output buffer to Press.bits
inCoreAddress ← InitScanBuffer[pa];--get enough space for a scan line; must call after InitTfsBuffer
MesaBands.ShowBands[];

ReleaseScanBuffer[FALSE, inCoreAddress, pa];--write out blank scan lines if last band is not full & free storage

WritePageGPage[pa!--get out if error
errorTfs => IF (e = tridentError)
THEN {WriteLine["Transfer Complete, but"L]; endReason ← tridentError; GOTO done}];
ReleaseTfsBuffer[];
ReleaseTfsBandsBuffer[];
CloseBandsFile[];--must call this before TfsCloseDisk[,FALSE] as it needs a disk descriptor
disk←TfsCloseDisk[disk, FALSE];
ddMgr ← NIL;
okToProceed ← TRUE;

EXITS
getOut=> NULL;
done=>
{
ReleaseScanBuffer[FALSE, inCoreAddress, pa];--write out blank scan lines if last band is not full & free storage
ReleaseTfsBandsBuffer[];
ReleaseTfsBuffer[];
SELECT endReason FROM
emptyBuffReason=>WriteLine["Empty Page: error!"L];
illegalReason =>WriteLine["illegal End."L];
tridentError =>WriteLine["Trident error"L];
hitEOF => WriteLine["Ran into EOF on write"L];
dANotFilled =>WriteLine["Trident software trouble -- bad DA multiple times"L];
ENDCASE;

SELECT endReason FROM
tridentError => NULL;
emptyBuffReason, hitEOF, dANotFilled => { CloseBandsFile[]; disk ← TfsCloseDisk[disk, FALSE]; ddMgr ← NIL};
ENDCASE;
};
END;
IF checkTermination THEN
IF ~okToProceed THEN CallDebugger["Exiting with error from GetBits"L];
END;
--of GetBitsFromBands
StoreScanLine: PUBLIC PROC [p: LONG POINTER]=
--Put scan line into Press.bits. Breaks scan line up if it overflows a Trident Page. Also pads the band out to 1K boundary.
--Now, if we overflow the Tfsbuffer, we automatically write out the full page and add remainder of scan to newly emptied buffer. If that was the last scan line of the buffer, we write out the partial page regardless whether we just flushed the full buffer since we’re padding the trident page at the end of a band. Hence the test for scanInBand at end.
{
wordsLeft: CARDINAL;

wordsLeft ← (TFSwordsPerPage-wordAddrInTfsBuffer);
LongCOPY[p, MIN[wordsLeft, scanLength], tfsBuff + wordAddrInTfsBuffer];

IF wordsLeft < scanLength--wordsLeft can be zero
THEN
{WriteTfsPage[];
LongCOPY[p+wordsLeft, wordAddrInTfsBuffer ← (scanLength-wordsLeft), tfsBuff];
}
ELSE wordAddrInTfsBuffer ← wordAddrInTfsBuffer + scanLength;--can = TFSwordsPerPage

IF (scanInBand ← scanInBand + 1) = bandWidth THEN
{WriteTfsPage[];
wordAddrInTfsBuffer ← 0;--reset wordAddrInTfsBuffer to 0 to avoid an empty page next go around
scanInBand ← 0;
};
};
--StoreScanLine

InitTrident
: PUBLIC PROC[ddMgrPt: ddMgrPtr ← NIL, iDisk: tfsdskPtr] RETURNS [disk: tfsdskPtr]=
BEGIN
IF ~uCodeLoaded THEN--load microcode
{RamBoot["MesaSlotMc.br"! CantFindFile => GOTO noUcode;
FileLooksCrufty =>GOTO badUcode];
uCodeLoaded ← TRUE;};
IF iDisk # NIL THEN disk ← TfsCloseDisk[iDisk, TRUE];
disk ← TfsInit[TRUE,, ddMgrPt,];--initmode=TRUE, drive, ddMgr, freshDisk=FALSE

EXITS
noUcode => WriteLine["Can’t find file MesaSlotMc.br."L];
badUcode => WriteLine["Microcode file ""MesaSlotMc.br"" is malformed."L];
END;--
of InitTrident

GetTfsBuffer:
PROC[]=
{
IF tfsSeg # NIL THEN DeleteDataSegment[tfsSeg];
tfsSeg ← NewDataSegment[DefaultBase, (TFSwordsPerPage + PageSize-1)/PageSize];
tfsBuff ← SegmentAddress[tfsSeg];
pages ← [fillInDA, fillInDA, fillInDA, fillInDA, fillInDA, fillInDA];
dAsLength ← pagesLength;--this varies with the bits file writing
};--
GetTfsBuffer

InitTfsBuffer
: PROC[file: OutputFile]=
{
--Call this routine only after calling GetTfsBuffer!
--this routine assumes we’re writing.
nmChars: CARDINAL ← 0;
dAs: DESCRIPTOR FOR ARRAY OF PAGE ← DESCRIPTOR[@pages[1], dAsLength];
dAs[0] ← leaderVda;
dAs[1] ← firstVda;
[]← TfsActOnPages[disk, NIL, dAs, filePtr↑, 1, 2, dcReadLnD, @nmChars, dcReadLnD, @nmChars, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, TRUE, 0];--leave the VDA to pages 2 and 3 in the array

outputFile ← file;--let CloseTfsBuffers know not to truncate
SELECT file FROM
anyOtherFile=> pageNum ← 1;
bitsFile=>pageNum ← 2;--begin writing the bits file at page 2.
ENDCASE;
dAsBase ← @pages[1];
};
--InitTfsBuffer

GetTfsBandsBuffer:
PUBLIC PROC[] RETURNS[POINTER]=
{
RETURN[bandDiskBuffer]};--GetTfsBandsBuffer

CheckPage:
PROC[p: PAGE, both: BOOLEAN ← TRUE] RETURNS [notOK: BOOLEAN ← FALSE]=
{
IF p = fillInDA
THEN--the vda is not valid
IF debuggerIfTfsError
THEN CallDebugger["next disk address is fillInDA"L]
ELSERETURN[TRUE];
IF ~both THEN RETURN[notOK];
IF p = eofDA
THEN--the vda is not valid
IF debuggerIfTfsError
THEN CallDebugger["next disk address is eofDA"L]
ELSERETURN[TRUE];
};


WriteTfsPage
: PROC[wordCt: TfsMaxWords ← TFSwordsPerPage]=
--This routine writes only full pages!!!!!
--Don’t let this routine extend Press.bits unless extension is contiguous.
{endReason: EndReason ← illegalReason;
nmChars: CARDINAL ← BytesPerWord*wordCt;

dAs: DESCRIPTOR FOR ARRAY OF PAGE ← DESCRIPTOR[dAsBase, dAsLength];
BEGIN
IF ((lastPageChars ← nmChars) # TfsCharsPerPage) THEN GOTO nullExit;--let CloseTfsBuffers clean up
IF CheckPage[dAs[pageNum], TRUE] THEN {endReason ← dANotFilled; GOTO done};

dAs[pageNum+1] ← fillInDA;dAs[pageNum+2] ← fillInDA;--so as to get the real VDA’s
--since we’re writing a full page, will need a page following, even if it turns out to be of length zero (last page of file).
[]←TfsWritePages[disk, NIL, dAs, filePtr↑, pageNum, pageNum+1, dcReadLD, NIL, TfsCharsPerPage, tfsBuff, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, TRUE, 0!
BadErrorRtn => {endReason ← tridentError; GOTO done;};];

dAs[pageNum-1] ← dAs[pageNum]; dAs[pageNum] ← dAs[pageNum+1]; dAs[pageNum+1] ← dAs[pageNum+2];

dAsLength ← dAsLength + 1;--extend range of descriptor from new base
dAsBase ← dAsBase - 1;--must reset base because the low-level disk routines write pageNum onto
pageNum ← pageNum + 1;-- the disk label; and the vda is accessed from dAs using pageNum!

EXITS
done=>
SELECT endReason FROM
illegalReason =>WriteLine["illegal End."L];
tridentError, hitEOF, dANotFilled =>errorTfs[endReason];
ENDCASE;
nullExit=> NULL;
END;
};--WriteTfsPage


ReleaseTfsBuffer: PROC[]=
{
IF tfsSeg # NIL THEN
DeleteDataSegment[tfsSeg];
tfsSeg ← NIL;
}
;--ReleaseTfsBuffer

CloseTfsBuffers:
PROC[]=
--this routine never writes full pages; writes partial or zero-length pages only.
--It also never extends the file. All file extension is done in WriteTfsPage.


BEGIN
dAs: DESCRIPTOR FOR ARRAY OF PAGE ← DESCRIPTOR[dAsBase, dAsLength];
lastPage: CARDINAL ← pageNum;--this guy is guaranteed to be there.
nmChars: CARDINAL ← 0;
leaderChars: CARDINAL ← TfsCharsPerPage;
lastDA, toDelete: PAGE;
ld: POINTER TO LD ← LOOPHOLE[tfsBuff];

IF outputFile = bitsFile THEN GOTO getout;--don’t truncate press.bits
IF ~(lastPageChars = TfsCharsPerPage)THEN nmChars ← lastPageChars;
[] ← CheckPage[dAs[lastPage], FALSE];--error if dAs[lastPage]= fillInDA

--the value in dAs[lastPage+1] was filled in by the two-page write in WriteTfsPage
toDelete ← dAs[lastPage + 1]; dAs[lastPage + 1] ← eofDA;--for label
[]←TfsWritePages[disk, NIL, dAs, filePtr↑, lastPage, lastPage, dcWriteD, @nmChars, nmChars, tfsBuff, NIL, DefaultTfsErrorRtn, NIL, 0];
TfsDeletePages[disk, tfsBuff, toDelete, filePtr↑, , lastPage+1,];

--read in leader page and fix hintLastPageFa
lastDA ← dAs[lastPage];
dAs[0] ← eofDA; leaderChars ← TfsCharsPerPage;
dAs ← DESCRIPTOR[dAsBase+1, dAsLength-1]; dAs[0] ← leaderVda; dAs[1] ← fillInDA;
[] ← TfsActOnPages[disk, NIL, dAs, filePtr↑, 0, 0, dcReadLD, @leaderChars, dcReadLD, tfsBuff, NoopTfsCleanupRtn, , TRUE, 0];
ld.hintLastPageFa ← FA[lastDA, lastPage, nmChars];
[] ← TfsActOnPages[disk, NIL, dAs, filePtr↑, 0, 0, dcWriteD, @leaderChars, dcWriteD, tfsBuff, NoopTfsCleanupRtn, , TRUE, 0];
ReleaseTfsBuffer[];

EXITS
getout =>
ReleaseTfsBuffer[];

END;
--CloseTfsBuffers

InitScanBuffer: PROC[pa: PageAttributes] RETURNS [coreAddress: POINTER]=
{
padding: CARDINAL;

IF scanSeg # NIL THEN DeleteDataSegment[scanSeg];
scanSeg ← NewDataSegment[DefaultBase, (pa.bitWc + PageSize-1)/PageSize];
coreAddress ← SegmentAddress[scanSeg];

scanInBand ← wordAddrInTfsBuffer ← 0;--init the scan line # we’re on
scanLength ← pa.bitWc;

--will never need more than bandWidth scans
IF (padding ← pa.firstScan MOD bandWidth) > 0 THEN
{Zero[coreAddress, pa.bitWc];
FOR i: CARDINAL IN [0..padding)
DO StoreScanLine[coreAddress]; ENDLOOP;
};

};
--InitScanBuffer

ReleaseScanBuffer
: PROC[aborting: BOOLEAN ← FALSE, address: POINTER, pa: PageAttributes]=
--Pads the first and last bands with blank scan lines if, for instance, firstScan is not = to a (multiple of bandWidth + 1)
BEGIN
padding: CARDINAL;

IF ~aborting THEN
{padding ← pa.lastScan MOD bandWidth;
IF padding # bandWidth-1 THEN
{Zero[address, pa.bitWc];
FOR i: CARDINAL IN [1..bandWidth-padding)--output bandWidth-padding-1 lines
DOStoreScanLine[address];
ENDLOOP};};

DeleteDataSegment[scanSeg];
scanSeg ← NIL;
END
;--ReleaseScanBuffer


TridentThere: PROC[]=
{
IF ddMgr = NIL THEN ddMgr ← TfsCreateDDmgr[];
disk ← InitTrident[ddMgr, disk];--loads disk object

IF disk = NIL THEN ERROR errorTfs[noTrident];
};--TridentThere


OpenPressBits
: PROC[filePtr: POINTER TO FP]=
{
TridentThere[];
OpenAppropriateFile[bitsStr, filePtr];
};--
OpenPressBits

OpenAppropriateFile: PROC[fileName: STRING, filePtr: POINTER TO FP]=
--This routine deletes the global ddMgr if it can’t find Press.bits on the Trident. It also deletes the disk object.
--Thus, this routine must be called before calling OpenPressBands, as that routine assumes this routine has already succeeded.
BEGIN
fileSys: CARDINAL ← 1;--TP0:sys 1

[leaderVda, firstVda,] ← TfsOpenFile[disk, fileName, read, filePtr];--must fool Open with read. Only other option is create.
IF firstVda=0 AND disk.tfskd.model = 80 THEN --"not found" if not on 1st file system.
GOTO errorXit;

WHILE firstVda = 0 AND fileSys < 23 --check all filesystems on a T300
DO--drives 0-7 and 3 filesystems/drive
IF disk # NIL THEN
disk←LOOPHOLE[TfsCloseDisk[disk, TRUE]];--keep ddMgr, and make disk NIL
disk ← TfsInit[TRUE, BITOR[BITSHIFT[(fileSys MOD 3), 8], (fileSys/3)], ddMgr,];
fileSys ← fileSys + 1;
IF disk = NIL THEN LOOP;
[leaderVda, firstVda, ] ← TfsOpenFile[disk, fileName, read, filePtr];
ENDLOOP;

IF firstVda = 0 THEN
GOTO errorXit;--not anywhere on T300

EXITS
errorXit =>
{IF disk # NIL THEN disk ← TfsCloseDisk[disk, FALSE];
ddMgr ← NIL;
ERROR errorTfs[cantFindFile]};
END;
--OpenAppropriateFile

WritePageGPage: PROC[pa: PageAttributes]=
--can raise errorTfs[tridentError]
{pageBuf: ARRAY[0..TFSwordsPerPage) OF WORD; --Plug in PageG info and write this buffer to disk
firstPage: POINTER TO FirstPage ← LOOPHOLE[@pageBuf[0]];
nmChars: CARDINAL ← BytesPerWord*TFSwordsPerPage;

dAs: DESCRIPTOR FOR ARRAY OF PAGE ← DESCRIPTOR[@pages[1], dAsLength];
dAs[1] ← firstVda;

Zero [@pageBuf[0], TFSwordsPerPage];

firstPage.nPages ← 1;
firstPage.pageGSize ← SIZE[PageG];
firstPage.printerMode ← (IF pa.scanDirection = portrait THEN 3 ELSE 8);
firstPage.password ← PressPassword;
firstPage.pageGs[0].FirstBand ← pa.firstScan/bandWidth;
firstPage.pageGs[0].LastBand ← pa.lastScan/bandWidth;
firstPage.pageGs[0].BitMargin ← pa.margin;
firstPage.pageGs[0].BitWc ← pa.bitWc;
firstPage.pageGs[0].BitPage ← 1;--i.e., first page after the firstPge
firstPage.pageGs[0].PageNumber ← 1;--i.e., from first page of Press file

[]← TfsActOnPages[disk, NIL, dAs, filePtr↑, 1, 1, dcWriteD, @nmChars, dcWriteD, @pageBuf[0], DefaultTfsCleanupRtn, DefaultTfsErrorRtn, TRUE, 0!
BadErrorRtn => GOTO done];

EXITS
done => errorTfs[tridentError];
};
--WritePageGPage

CloseServerConnection: PROC[]=
{
IF ~gotAJob THEN GOTO done;

EFTPFinishReceiving[!
EFTPNotReceiving => CONTINUE];--acknowledge to sender.
PupPackageDestroy[];
gotAJob ← pupPkgExtant ← connectionOpen ← FALSE;

EXITS
done => NULL;
};
--CloseServerConnection


END.
-- PressNetListener.mesa
-- Last Edited: October 27, 1981 4:35 PM By: GWilliams
-- added code to try for the next vda again if not filled by TfsActOnPages the first -- Last Edited: October 27, 1981 3:12 PM By: GWilliams
-- added debuggerIfTfsError
-- Last Edited: October 26, 1981 2:38 PM By: GWilliams
-- added check that filled-in DA is valid at GetBits & added EFTPFinishReceiving.
-- Last Edited: October 26, 1981 10:54 AM By: GWilliams
--added fileLengthReport
-- Last Edited: October 27, 1981 5:17 PM By: GWilliams
-- put check at end of GetBits to stop if not continuing
-- Last Edited: November 24, 1981 3:04 PM By: GWilliams
-- In middle of revamping to accept bits on a scan line basis rather than read a whole Press.bits file.
-- Last Edited: December 2, 1981 11:16 AM By: GWilliams
-- Back again - - took time out to help Starkweather & to write Performance appraisal.
-- Last Edited: December 8, 1981 6:03 PM By: GWilliams
-- Back again - - Press.fonts broke, now debugging.
-- Last Edited: December 9, 1981 4:38 PM By: GWilliams
-- Fixing OpenPressBits for when can’t find Press.bits on T300.
-- Last Edited: December 10, 1981 4:24 PM By: GWilliams
-- In InitTfsBuffer, was loading vda of 2nd page of bits file with firstVda.
-- Last Edited: December 21, 1981 3:49 PM By: GWilliams
-- Changed CloseServerConnection to not do EFTPFinishReceiving on closing.
-- Last Edited: December 21, 1981 5:04 PM By: GWilliams
-- Changed GetBits to ask for more data than needed in order to wait for sender disconnect.
-- Last Edited: December 31, 1981 3:17 PM By: GWilliams
-- Changed ordering of call on InitTfsBuffer and InitScanBuffer.
-- GetBits is called by Press.mesa
-- Last Edited: February 8, 1982 11:22 AM By: GWilliams
-- WritePageGPage now gets printerMode from pageAttributes record sent from client.
-- Last Edited: March 5, 1982 3:48 PM By: GWilliams
-- Added Press Bands code to read Cedar bands file entries and explode into press.bits.
-- Last Edited: March 8, 1982 1:59 PM By: GWilliams
-- Refining Bands code: clean up bits file disk object if fail in openning band sfile.
-- Last Edited: July 9, 1982 3:11 PM By: GWilliams
-- Changing to 1) listen for both Press files and Bands files 2) in doing so, must possibly extend TridentTemp.press, or shorten it.
-- Last Edited: July 15, 1982 3:20 PM By: GWilliams
-- Last Edited: August 13, 1982 4:37 PM By: GWilliams
-- faking out TfsWritePages by shoving in an EOFDA at end of file.
-- Last Edited: August 16, 1982 6:47 PM By: GWilliams
-- must now write the leader page to keep the file current for BFS and TFS.
-- Last Edited: August 31, 1982 10:45 AM By: GWilliams
-- Had trouble linking new pages in the file system, need to keep file one page longer than current page, as in the Streams code.
-- Last Edited: September 1, 1982 11:07 AM By: GWilliams
-- Still linking new pages @end of file, do it by writing previous header over when adding new page.
-- Last Edited: November 17, 1982 4:03 PM By: GWilliams
-- Debugging again.
-- Last Edited: November 19, 1982 7:06 PM By: GWilliams
-- Restructuring GetBits for clarity, debugging page writing.
-- Last Edited: January 10, 1983 5:10 PM By: GWilliams
-- Make it more like the TFS Streams stuff.