-- File: PressNetListener.mesa: Routines for getting for a file at a printing server.
-- GetBits is called by Press.mesa
-- Last Edited: March 22, 1982 4:01 PM By: GWilliams
-- Adding Stream mechanism for transporting data.
DIRECTORY
AltoDefs USING [BytesPerWord, PageSize],
AltoRam USING [CantFindFile, FileLooksCrufty],
IODefs USING[CR, SP, 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, veryLongWait],
PupStream USING [AppendPupAddress, CreatePupByteStreamListener, DestroyPupListener, PupListener, RejectThisRequest, StreamClosing],
PupTypes USING[PupAddress, PupSocketID],
SegmentDefs USING[DataSegmentHandle, DefaultBase, DeleteDataSegment, NewDataSegment, SegmentAddress],
Stream USING [Block, CompletionCode, EndOfStream, GetBlock, Handle, PutBlock, SendNow, SetInputOptions, SubSequenceType ],
TridentDefs USING [BadErrorRtn, dcReadLD, dcWriteD, ddMgrPtr, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, eofDA, fillInDA, FP, PAGE, TfsActOnPages, TfsCloseDisk, TfsCreateDDmgr, tfsdskPtr, TfsInit, TfsOpenFile, TFSwordsPerPage];
PressNetListener: MONITOR
IMPORTS AltoRam, IODefs, InlineDefs, MesaBands, MiscDefs, PressDefs, PressBandsDefs, PupDefs, PupStream, SegmentDefs, Stream, TridentDefs
EXPORTS PressBandsDefs, PressNetDefs =
BEGIN OPEN AltoDefs, AltoRam, IODefs, InlineDefs, MiscDefs, PressDefs, PressBandsDefs, PressNetDefs, PupDefs, PupStream, PupTypes, SegmentDefs, Stream, TridentDefs;
TerminationReason: TYPE = {errorTermination, fileDoneTermination, pageDoneTermination, nullTerminationReason};

--Press Stuff
bandWidth: CARDINAL = 16;
FirstPage: TYPE = MACHINE DEPENDENT RECORD
[nPages: CARDINAL ← 1,
pageGSize: CARDINAL ← SIZE[PageG],
printerMode: CARDINAL,--3=portrait, 8=Landscape
password: CARDINAL ← PressPassword,
pageGs: ARRAY[0..92) OF PageG--enough to fit into a Trident Page
];
scanSeg: DataSegmentHandle ← NIL;
scanLength: CARDINAL;
wordAddrInTfsBuffer: CARDINAL;
scanInBand: CARDINAL;

--
net stuff
listener: PupListener ← NIL;
connectionOpen: BOOLEAN ← FALSE;
gotAJob: BOOLEAN ← FALSE;
hostAddress: PupAddress;
pupPtr: POINTER TO PupAddress ← @hostAddress;
senderAddress: PupAddress;
receiverH: Stream.Handle;
pupPkgExtant: BOOLEAN ← FALSE;
--bufferPoolSize: CARDINAL ← 15;
--
bufferSize: CARDINAL ← 266;

--Process Stuff
connectionC: CONDITION;

--Tfs stuff
bandDiskBuffer: POINTER;
ddMgr: PUBLIC ddMgrPtr ← NIL;
disk: tfsdskPtr ← NIL;
bufferWordLen: CARDINAL = TFSwordsPerPage;
bufferByteLen: CARDINAL = BytesPerWord*bufferWordLen;
pagesLength: CARDINAL = 4;
firstVda: CARDINAL ← 0;--allways holds page 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;

--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;

--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;

GetBits: PUBLIC PROC[] RETURNS[okToProceed: BOOLEAN ← FALSE]=
--Raises no signals or errors
BEGIN
pa: PageAttributes;
endReason: EndReason ← illegalReason;
iii: CARDINAL;--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
IF ~FirstPageCheck[] THEN RETURN[FALSE];
WHILE ~receivedFile
DO
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--];

pa ← GetAJob[! errorComm => IF e = alreadyReceiving THEN {PupPackageDestroy[]; GOTO getOut}];
InitTfsBuffer[];
inCoreAddress ← InitScanBuffer[pa];--get enough space for a scan line; must call after InitTfsBuffer
scanLineLength ← scanLength;--scan Length is valid now.
BEGIN ENABLE BEGIN
errorComm =>
{SELECT e FROM
noisyChannel => {WriteLine["Noisy Channel, aborting transfer"L];
AbortReceiving["Channel too noisy, aborting transfer"L]};
endReceiving => WriteLine["Transfer aborted, not enough data received"L];
ENDCASE;
GOTO incompleteXFer};
errorTfs => SELECT e FROM tridentError, hitEOF, dANotFilled => {endReason ← e; GOTO done}; ENDCASE;
END;--of catch series

FOR iii IN [0..pa.lastScan-pa.firstScan]
DO
wordsInBuff ← GetBuffer[inCoreAddress, 1];--check header word
IF inCoreAddress[0] # imageCode THEN
{WriteLine["Buffer doesn’t contain image data"L]; GOTO incompleteXFer};

wordsInBuff ← GetBuffer[inCoreAddress, scanLineLength];--get scan line
IF wordsInBuff = 0 THEN {endReason ← emptyBuffReason; GOTO done};--blow up
StoreScanLine[inCoreAddress];--buffers data and writes to disk.
ENDLOOP;

EXITS
incompleteXFer =>
{IF checkTermination THEN
CallDebugger["File transfer trouble"];
CloseServerConnection[];
disk←TfsCloseDisk[disk, FALSE];--delete the ddMgr too
ddMgr ← NIL;
ReleaseScanBuffer[TRUE, inCoreAddress, pa];
ReleaseTfsBuffer[];
LOOP};--restart @ WHILE ~ receivedFile
END;

--now loop asking for data, waiting for an EFTPEndReceiving
BEGIN ENABLE errorComm => IF e = endReceiving THEN GOTO closeConn;
DO wordsInBuff ← GetBuffer[inCoreAddress, scanLineLength]; tooMuchData ← TRUE;
ENDLOOP;
EXITS
closeConn => NULL;
END;

CloseServerConnection[];--turn off net driver
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[];
disk←TfsCloseDisk[disk, FALSE];
ddMgr ← NIL;
receivedFile ← TRUE;
ENDLOOP;
okToProceed ← TRUE;

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

CloseServerConnection[];--turn off net if on.
SELECT endReason FROM
tridentError => NULL;
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

AbortReceiving: PROC[s: STRING]=
BEGIN
IF ~connectionOpen THEN RETURN;
AbortReceivingLocked[s];

END;

AbortReceivingLocked: ENTRY PROC[s: STRING]=
{
startIndex: CARDINAL ← 0;
stopIndexPlusOne: CARDINAL ← s.length;

block: Stream.Block ← [@s.text, startIndex, stopIndexPlusOne];
Stream.PutBlock[receiverH, block, FALSE!
EndOfStream => {CallDebugger["Got end of stream on put after end of stream"L];
CONTINUE}];
SendNow[receiverH];
};
--AbortReceivingLocked

AwaitConnection
: ENTRY PROC[]=
{
WHILE ~connectionOpen DO WAIT connectionC ENDLOOP;};

FinishReceiving: ENTRY PROC[]=
{
receiverH.delete[receiverH];
connectionOpen ← FALSE;--connectionOpen=FALSE enables new clients

};
--FinishReceiving

GetAJob: PROC[] RETURNS [pa: PageAttributes]=
{
typedMessage: BOOLEAN ← FALSE;
getAJobEndReason: EndReason ← illegalReason;
code: CARDINAL;
wordsReturned: CARDINAL;
pupAddressString: STRING ← [30];

IF gotAJob THEN ERROR errorComm [alreadyHaveJob, , ];
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
--only spawn one listener per entry to this proc.
listener ← CreatePupByteStreamListener[pupPtr.socket, PrintRequest, veryLongWait, RfcFilter];
};
};
WHILE ~gotAJob DO
--we don’t have a connection here, just a listener.
WriteLine["Listening for connection"L];
AwaitConnection[];

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

[wordsReturned] ← GetBuffer[@code, 1!
errorComm =>
SELECT e FROM
noisyChannel, protocolError, endReceiving=>
{FinishReceiving[]; connectionOpen ← FALSE; LOOP};
ENDCASE;];--get code to see if it is a Page Attributes code

IF code # attributesCode THEN
{AbortReceiving["I Expect Page Attributes first"];
WriteLine["Connection Refused, protocol error."L];
FinishReceiving[];
typedMessage ← FALSE;--connectionOpen=FALSE enables new clients
LOOP};--get rid of this customer & type init message

--the other process is really getting the stream data now.
wordsReturned ← GetBuffer[@pa, SIZE[PageAttributes]!
errorComm =>
SELECT e FROM
noisyChannel, protocolError, endReceiving=>
{FinishReceiving[]; LOOP};
ENDCASE;];

gotAJob ← TRUE;
ENDLOOP;
};
--GetAJob

PrintRequest:
ENTRY PROC[s: Stream.Handle, addr: PupAddress]=
{
receiverH ← s;
senderAddress ← addr;
SetInputOptions[s, [FALSE, FALSE, FALSE, FALSE, TRUE]];--signal on EndOfStream
NOTIFY connectionC;
};
--PrintRequest

RfcFilter:
PROC[pupAdr: PupAddress]=
{
IF connectionOpen THEN RejectThisRequest["Busy with another client, try later"L];
connectionOpen ← TRUE;
};
--RfcFilter
FirstPageCheck
: PROC [] RETURNS[goAhead: BOOLEAN ← TRUE]=
{
IF SIZE[FirstPage] > TFSwordsPerPage THEN
{WriteLine["First page description exceeds Trident Page Length"];
RETURN[FALSE]};
};
--FirstPageCheck
GetBuffer: ENTRY PROC[buffer: POINTER, len: CARDINAL] RETURNS [wordsInBufCt: CARDINAL ← 0]=
--copy from net Stream to buffer len amount of words
BEGIN
getABuffEndReason: EndReason ← illegalReason;
why: CompletionCode;
sst: SubSequenceType;
bufferPos: POINTER ← buffer;
byteLen: CARDINAL ← len*2;
block: Stream.Block ← [buffer, 0, byteLen];
bytesGotten: CARDINAL ← 0;

BEGIN

UNTIL block.startIndex = byteLen
DO
[bytesGotten, why, sst] ← Stream.GetBlock[receiverH, block!
EndOfStream => {getABuffEndReason ← doneReason; GOTO done};
StreamClosing => IF why=remoteClose THEN {getABuffEndReason ← doneReason; GOTO done}];

block.startIndex ← block.startIndex + bytesGotten;

ENDLOOP;
RETURN[BITSHIFT[block.startIndex, -1]];--divide by bytes/word

EXITS
done=>
{--CloseServerConnection[]; - - this is done at the catch phrase higher up.
wordsInBufCt ← BITSHIFT[block.startIndex + bytesGotten, -1];

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


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;

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];
InitTfsBuffer[];--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[];
--reset wordAddrInTfsBuffer to 0 to avoid an empty page next go around
wordAddrInTfsBuffer ← 0;
scanInBand ← 0;
};
};
--StoreScanLine
WriteTfsPage: PROC[]=
{
endReason: EndReason ← illegalReason;
loopCtr: CARDINAL;--this detects infinite loops in GetBits
maxTries: CARDINAL = 3;
nmChars: CARDINAL ← BytesPerWord*TFSwordsPerPage;

dAs: DESCRIPTOR FOR ARRAY OF PAGE ← DESCRIPTOR[dAsBase, dAsLength];
BEGIN
IF (dAs[pageNum] ← dAs[pageNum+1]) = eofDA
THEN{endReason ← hitEOF; GOTO done;};--by now the vda of the next page to write is in

IF (dAs[pageNum] = fillInDA)
THEN--the vda is not valid
IF debuggerIfTfsError
THEN CallDebugger["disk address is fillInDA"L]
ELSE{endReason ← dANotFilled; GOTO done};

dAs[pageNum+1] ← fillInDA;--reset the to-be-pagenum+1 vda
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!
dAs ← DESCRIPTOR[dAsBase, dAsLength];
--TypeOutStatus[dAs, pageNum, charsInPage, TRUE];----the TRUE means "before ActOnPages"
[]← TfsActOnPages[disk, NIL, dAs, filePtr↑, pageNum, pageNum, dcWriteD, @nmChars, dcWriteD, tfsBuff, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, TRUE, 0!
BadErrorRtn => {endReason ← tridentError; GOTO done;};];
--TypeOutStatus[dAs, pageNum, charsInPage, FALSE];----the FALSE means "after ActOnPages"

loopCtr ← 0;
UNTIL dAs[pageNum+1] # fillInDA
DO--the Default TfsCleanupRtn didn’t fill in the next DA, try again, but don’t write data this time
IF (loopCtr ← loopCtr + 1) > maxTries
THEN
IF debuggerIfTfsError
THENCallDebugger["disk address is fillInDA after some retries"L]
ELSE{endReason ← dANotFilled; GOTO done};
IF dAs[pageNum+1] = eofDA THEN EXIT;
[]←TfsActOnPages[disk, NIL, dAs, filePtr↑, pageNum, pageNum, dcReadLD, @nmChars, dcReadLD, tfsBuff, DefaultTfsCleanupRtn, DefaultTfsErrorRtn, TRUE, 0!
BadErrorRtn => {endReason ← dANotFilled; GOTO done;};];
ENDLOOP;
EXITS
done=>
SELECT endReason FROM
illegalReason =>WriteLine["illegal End."L];
tridentError, hitEOF, dANotFilled =>errorTfs[endReason];
ENDCASE;
END;
};--WriteTfsPage

InitTrident: PUBLIC PROC[ddMgrPt: ddMgrPtr ← NIL, iDisk: tfsdskPtr] RETURNS [disk: tfsdskPtr]=
BEGIN

--
load microcode
IF ~uCodeLoaded THEN
{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

InitTfsBuffer
: PROC[]=
{
IF tfsSeg # NIL THEN DeleteDataSegment[tfsSeg];
tfsSeg ← NewDataSegment[DefaultBase, (TFSwordsPerPage + PageSize-1)/PageSize];
tfsBuff ← SegmentAddress[tfsSeg];
pages ← [fillInDA, fillInDA, fillInDA, fillInDA, fillInDA];
dAsLength ← pagesLength;--this varies with the bits file writing
--in next line, we are assuming that Press.bits is contiguous!!!!
pages[2] ← firstVda + 1;--this will be accessed as dAs[pageNum+1] to set up dAs[pageNum]
dAsBase ← @pages[0];
pageNum ← 1;--this gets incremented before using
};
--InitTfsBuffer

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

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

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


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


OpenPressBits: PROC[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


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

IF disk = NIL THEN ERROR errorTfs[noTrident];

[, firstVda,] ← TfsOpenFile[disk, "Press.bits.", 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;
[, firstVda, ] ← TfsOpenFile[disk, "Press.bits.", 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;
--OpenPressBits

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

receiverH.delete[receiverH];--this hopefully destroys the PrintRequest that was detached by the pupListener.
DestroyPupListener[listener];
listener ← NIL;
PupPackageDestroy[];
gotAJob ← pupPkgExtant ← connectionOpen ← FALSE;

EXITS
done => NULL;
};
--CloseServerConnection

TypeOutStatus
: PROC[dAs: DESCRIPTOR FOR ARRAY OF PAGE, pageNum, charsInPage: CARDINAL, beforeActOnPages: BOOLEAN ← TRUE]=
{--for debugging
i: CARDINAL;--debugging variable

IF ~dasMonitor THEN RETURN;
IF beforeActOnPages
THEN WriteLine["Before ActOnPages"L]
ELSE WriteLine["After ActOnPages"L];
WriteString["page number: "L];
WriteDecimal[pageNum]; WriteChar[CR];
IF beforeActOnPages
THEN {WriteString["Before ActOnPages -- chars received from GetAPage: "L];
WriteDecimal[charsInPage]; WriteChar[CR];};

WriteLine["dAs[0]..dAs[dAsLength] (length changes with page#)"];
FOR i IN [0..dAsLength) DO
WriteOctal[dAs[i]]; WriteChar[SP]; WriteChar [SP]; ENDLOOP;
WriteChar[CR]; WriteChar[CR];
};--
TypeOutStatus


--initialization (for debugging only)
--filePtr ← @fp; Use this if Mesa doesn’t allow startup assignment

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: March 10, 1982 11:19 AM By: GWilliams
-- Integrating Bands expanding code.