-- FileStreamCreateImpl.mesa
-- Please maintain change log at end of file.
-- Last Edited by
-- Hagmann on December 6, 1983 4:53 pm
-- Schroeder on November 28, 1983 12:37 pm

-- To Do:
-- What to do when byte length > allocated length at Open time?


DIRECTORY
BasicTime USING [GMT],
Basics USING [LongNumber, BITAND],
FS,
FileStream ,
FileStreamPrivate ,
FSBackdoor USING [ProduceError],
FSLock USING [RecordREF ],
Process USING [ Pause ],
IO,
IOUtils,
Rope,
SafeStorage USING [EnableFinalization],
VM USING [ AddressForPageNumber, Allocate, BytesForPages, CantAllocate,
    Free, PageNumber]
;

FileStreamCreateImpl: CEDAR MONITOR
LOCKS fileData.lockRecord USING fileData: FileDataHandle
IMPORTS
Basics,
FileStream,
FileStreamPrivate,
FS,
FSBackdoor,
FSLock,
IO,
IOUtils,
Process,
SafeStorage,
VM
EXPORTS
FileStream =
BEGIN OPEN Basics;
ROPE: TYPE = Rope.ROPE;
STREAM: TYPE = IO.STREAM;
ByteCount: TYPE = INT;
ByteNumber: TYPE = ByteCount; -- index rather than count
PageNumber: TYPE = VM.PageNumber;
PageCount: TYPE = VM.PageNumber;

bytesPerFilePage: CARDINAL = FS.BytesForPages[1];
maxVMPagesPerBuffer: INT = 65536/VM.BytesForPages[pages: 1] ;

clearLowBits: CARDINAL = CARDINAL.LAST-(bytesPerFilePage-1);

Data: TYPE = FileStreamPrivate.Data;
FSDataHandle: TYPE = FileStreamPrivate.FSDataHandle;
BufferNode: TYPE = FileStreamPrivate.BufferNode;
BufferNodeHandle: TYPE = FileStreamPrivate.BufferNodeHandle;
FileDataHandle: TYPE = FileStreamPrivate.FileDataHandle;
FileData: TYPE = FileStreamPrivate.FileData;
ProcHandle: TYPE = REF IO.StreamProcs;


     -- This code does not protect itself from parallel use of a stream by concurrent
     -- processes. It assumes that the processes will synchronize at a higher level.
     -- Parallel use of different streams for the same open file is expected, but the
     -- read/write stream must be opened by StreamOpen or StreamFromOpenFile,
     -- and read stream by StreamFromOpenStream.
     
-- Stream creation

StreamFromOpenFile: PUBLIC PROC [
openFile: FS.OpenFile,
accessRights: FS.Lock,
initialPosition: FS.InitialPosition,
streamOptions: FS.StreamOptions,
streamBufferParms: FS.StreamBufferParms,
extendFileProc: FS.ExtendFileProc]
RETURNS [stream: STREAM] = {
  -- no monitors are needed in this code since, until this proc returns,
  -- no other code can refer to the streams
pageAllocation: PageCount;
byteLength: ByteCount;
fileName: ROPE = openFile.GetName[].fullFName;
fsData: FSDataHandle;
fsDataFile: FileDataHandle ;
node: BufferNodeHandle ;
   -- Index must always be less than 64K, so we have to clip off a page from the max.
IF streamBufferParms.vmPagesPerBuffer = 128 THEN
streamBufferParms.vmPagesPerBuffer ← 127 ;
IF accessRights = $write AND GetFileLock[openFile] # $write
THEN FSBackdoor.ProduceError[wrongLock, fileName];
[pages: pageAllocation, bytes: byteLength] ← openFile.GetInfo[];
fsData ← NEW[Data ← []
];
fsDataFile ← NEW[FileData ← [
 fileName: fileName,
 accessRights: accessRights,
 fileLength: byteLength,
 fileHandle: openFile,
 streamBufferParms: streamBufferParms,
 extendFileProc: extendFileProc,
 streamOptions: streamOptions,
 byteLength: byteLength,
 byteSize: pageAllocation*bytesPerFilePage,
 validBytesOnDisk: byteLength]
];
IF fsDataFile.byteLength > fsDataFile.byteSize THEN ERROR;
fsData.fileData ← fsDataFile ;
fsDataFile.firstBufferNode ← node ←
CreateBufferSpace[vmPagesPerBuffer: streamBufferParms.vmPagesPerBuffer];
FOR i: INT IN [2..streamBufferParms.nBuffers] DO
 node.nextBufferNode ←
  CreateBufferSpace[vmPagesPerBuffer: streamBufferParms.vmPagesPerBuffer];
 node ← node.nextBufferNode ;
 ENDLOOP;
stream ← IO.CreateStream[FileStreamPrivate.ProcHandleFromAccessRights[accessRights], fsData];
IOUtils.StoreData[self: stream, key: $Name, data: fsDataFile.fileName];
IF accessRights = $write THEN {
 fsDataFile.writeStreamData ← fsData ;
 fsData.isWriteStream ← TRUE ;
 IF fsDataFile.byteSize = 0 THEN {
   fsDataFile.byteSize ← NewByteSize[fsDataFile.byteSize];
   SetFileSize[fsDataFile.fileHandle, fsDataFile.byteSize];
   };
  }
ELSE {
fsDataFile.firstReadStream ← fsData;
};
IF initialPosition = start THEN {
[] ← FileStreamPrivate.SetupBuffer[fileData: fsDataFile, fsData: fsData, fileByte: 0]
}
ELSE { -- initialPosition = end
node ← FileStreamPrivate.SetupBuffer[fileData: fsDataFile,
fsData: fsData, fileByte: PageContainingLastByte[fsDataFile.fileLength]];
fsData.index ← node.dataBytesInBuffer;
};
IF streamOptions[tiogaRead] AND byteLength > 0 THEN {
isTioga: BOOL; len: INT;
[yes: isTioga, len: len] ← IsThisThingATiogaFile[stream];
IF isTioga THEN {
IF accessRights = $read THEN {
-- make length look changed by sneaky call to SetLength (not in stream procs).
-- since stream is opened for read only, this call won't change the length in the file.
FileStream.SetLength[stream, len];
fsDataFile.tiogaReader ← TRUE
}
ELSE {
-- you can't incrementally update a Tioga file with IO!
stream.Close[];
FSBackdoor.ProduceError[cantUpdateTiogaFile, fileName];
}
}
};
IF FileStreamPrivate.DoFinalization THEN {
 FSLock.RecordREF[fsData];
 SafeStorage.EnableFinalization[fsData];
 };
fsData ← NIL ;
RETURN[stream];
};--StreamFromOpenFile

PageContainingLastByte: PROC [byteLen: INT] RETURNS [INT] = INLINE {
IF byteLen = 0 THEN RETURN[0] ELSE {
byteLen ← byteLen - 1;
LOOPHOLE[byteLen, LongNumber[num]].lowbits ←
BITAND[LOOPHOLE[byteLen, LongNumber[num]].lowbits, clearLowBits];
RETURN[byteLen] }};

OpenFileFromStream: PUBLIC PROC [self: STREAM] RETURNS [FS.OpenFile] = {
WITH self.streamData SELECT FROM
fsData: FSDataHandle => RETURN [fsData.fileData.fileHandle];
ENDCASE => ERROR IO.Error[NotImplementedForThisStream, self];
};

StreamFromOpenStream: PUBLIC PROC [self: STREAM] RETURNS [stream: STREAM] = {
  newData: FSDataHandle ;
  filePos: INT ;
  WITH self.streamData SELECT FROM
selfData: FSDataHandle => {
   fileData: FileDataHandle = selfData.fileData ;
   IF NOT selfData.isWriteStream OR fileData.firstReadStream # NIL THEN
    FSBackdoor.ProduceError [code: notImplemented,
     explanation: "self is not a write stream, or there already is a read stream"];
   newData ← NEW[Data ← [ ] ];
   newData.fileData ← fileData ;
   stream ← IO.CreateStream[FileStreamPrivate.ProcHandleFromAccessRights[$read],
    newData];
   IOUtils.StoreData[self: stream, key: $Name, data: fileData.fileName];
   fileData.firstReadStream ← newData;
   filePos ← SetUpClonedStream[fileData: fileData, fsData: selfData];
   [] ← FileStreamPrivate.SetupBuffer[fileData: fileData, fsData: newData,
    fileByte: selfData.currentNode.firstFileByteInBuffer] ;
   newData.index ← selfData.index ;
   IF FileStreamPrivate.DoFinalization THEN {
    FSLock.RecordREF[newData];
    SafeStorage.EnableFinalization[newData];
    };
   newData ← NIL ;
   };
  ENDCASE => ERROR IO.Error[NotImplementedForThisStream, self];
};

  

 SetUpClonedStream: ENTRY PROC [fileData: FileDataHandle, fsData: FSDataHandle]
  RETURNS [filePos: INT]= {
  ENABLE UNWIND => NULL;
  node: BufferNodeHandle ← fileData.firstBufferNode;
      -- Find last node
  UNTIL node.nextBufferNode = NIL DO
   node ← node.nextBufferNode ;
   ENDLOOP ;
      -- Allocate some more nodes.
  FOR i:INT IN [1..fileData.streamBufferParms.nBuffers] DO
  node.nextBufferNode ←
   CreateBufferSpace[vmPagesPerBuffer: fileData.streamBufferParms.vmPagesPerBuffer];
  node ← node.nextBufferNode ;
  ENDLOOP;
  fileData.numberOfStreams ← fileData.numberOfStreams + 1 ;
  filePos ← fsData.index + fsData.currentNode.firstFileByteInBuffer ;
  fsData ← NIL ;
  };

-- Buffer management

CreateBufferSpace: PROC [vmPagesPerBuffer: INT [1 .. 128]]
RETURNS [BufferNodeHandle] = {
 vmPages: INT ← MIN[vmPagesPerBuffer, maxVMPagesPerBuffer] ;
 newBuffer: BufferNodeHandle ← NEW[BufferNode];
 newBuffer.bufferInterval ← VM.Allocate[count: vmPages
  ! VM.CantAllocate => {
      -- We cannot accept anything but the right size interval.
      -- The program assumes that all buffers are the same size.
  TRUSTED {VM.Free[interval: bestInterval]};
  Process.Pause[4];
  RETRY;
  };
  ];
 TRUSTED{newBuffer.buffer ←
  VM.AddressForPageNumber[newBuffer.bufferInterval.page]};
 newBuffer.bufferBytes ← VM.BytesForPages[pages: vmPages] ;
 RETURN[newBuffer]
};


NewByteSize: PROC [byteCount: ByteCount] RETURNS [ByteCount] = {
RETURN [byteCount+5120];
};


-- Talking to FS


SetFileSize: PROC [f: FS.OpenFile, byteSize: ByteCount] = {
f.SetPageCount[pages: (byteSize+bytesPerFilePage-1)/bytesPerFilePage];
};

GetFileLock: PROC [f: FS.OpenFile] RETURNS [FS.Lock] = {
RETURN [f.GetInfo[].lock]
};


-- Tioga

IsThisThingATiogaFile: PROC [h: STREAM] RETURNS [yes: BOOL, len: INT] = {
pos, length: INT;
{ -- block so EXITS code can use pos, len, and length.
controlHeaderId: ARRAY [0..fileIdSize) OF CHAR = [235C,312C];
controlTrailerId: ARRAY [0..fileIdSize) OF CHAR = [205C,227C];
commentHeaderId: ARRAY [0..fileIdSize) OF CHAR = [0C,0C];
fileIdSize: NAT = 2;
numTrailerLengths: NAT = 3; -- <file-props-length> <data-length> <file-length>
endSize: NAT = fileIdSize+numTrailerLengths*4; -- trailer plus three lengths
ReadLen: PROC [h: STREAM] RETURNS [INT] = {
  start: PACKED ARRAY [0..3] OF CHARACTER;
  start[0] ← h.GetChar[]; start[1] ← h.GetChar[];
  start[2] ← h.GetChar[]; start[3] ← h.GetChar[];
  RETURN [LOOPHOLE[start]] };
 commentStart, commentLen, propsLen, controlLen, controlEnd: INT;
 pos ← h.GetIndex[]; -- save position to restore later
 length ← h.GetLength[]; -- length including any trailer stuff
 controlEnd ← length-endSize; -- where the trailer info starts
 IF controlEnd <= 0 THEN GOTO fail; -- too small
 h.SetIndex[controlEnd]; -- set up to read the trailer
 FOR i:NAT IN [0..fileIdSize) DO -- read the controlTrailerId
  IF h.GetChar[] # controlTrailerId[i] THEN GOTO fail;
  ENDLOOP;
 IF (propsLen ← ReadLen[h]) NOT IN [0..controlEnd) THEN GOTO fail;
 IF (commentStart ← ReadLen[h]) NOT IN [0..controlEnd) THEN GOTO fail;
 IF ReadLen[h] # length THEN GOTO fail;
 IF commentStart > 0 THEN { -- may have padded text with a null
  h.SetIndex[commentStart-1];
  len ← IF h.GetChar[]=0C THEN commentStart-1 ELSE commentStart }
 ELSE h.SetIndex[len ← commentStart];
 FOR i:NAT IN [0..fileIdSize) DO -- read the commentHeaderId
  IF h.GetChar[] # commentHeaderId[i] THEN GOTO fail;
  ENDLOOP;
 commentLen ← ReadLen[h]; -- the length of the comment section
 IF commentStart+commentLen NOT IN [0..controlEnd) THEN GOTO fail;
 h.SetIndex[commentStart+commentLen]; -- go to start of control info
 FOR i:NAT IN [0..fileIdSize) DO -- check the controlHeaderId
  IF h.GetChar[] # controlHeaderId[i] THEN GOTO fail;
  ENDLOOP;
 controlLen ← ReadLen[h]; -- the length of the control section
 IF commentStart+commentLen+controlLen # length THEN GOTO fail;
 GOTO succeed;
 EXITS
  fail => { h.SetIndex[pos]; RETURN [FALSE, length] };
  succeed => { h.SetIndex[pos]; RETURN [TRUE, len] };
 }};

END.


CHANGE LOG

Created by Hagmann on November 22, 1983 4:30 pm
-- By cutting this out of FSFileIOImpl.

Changed by Hagmann on November 28, 1983 12:01 pm
-- Added test for DoFinalization to enable FileStream testing without making a boot file

Changed by Hagmann on December 6, 1983 4:52 pm
-- Removed code for process cache