-- FileIOAlpineImpl.mesa
-- Last Edited by
--   MBrown on June 8, 1983 12:10 pm
--   Kolling on June 3, 1983 4:54 pm
  DIRECTORY
    AlpineEnvironment,
    AlpineInterimDirectory,
    AlpInstance,
    AlpTransaction,
    AlpFile,
    ByteBlt USING [ByteBlt],
    Environment USING [Block, Byte, bytesPerWord],
    FileIO,
    FileIOAlpine,
    FileIOPrivate,
    Inline USING [BITAND, BITOR, LongNumber, LowHalf],
    IO,
    RPC,
    Rope,
    Runtime USING [BoundsFault],
    SafeStorage USING [NarrowRefFault],
    Space USING [Create, Delete, Handle, LongPointer, Map, virtualMemory],
    System USING [GreenwichMeanTime, GetGreenwichMeanTime];
FileIOAlpineImpl:  CEDAR PROGRAM
  IMPORTS
    AlpineInterimDirectory,
    AlpTransaction,
    AlpFile,
    ByteBlt,
    FileIO,
    FileIOAlpine,
    FileIOPrivate,
    I: Inline,
    IO,
    RPC,
    Runtime,
    SafeStorage,
    Space,
    System
  EXPORTS
    FileIOAlpine,
    FileIOPrivate =
  BEGIN
  ROPE: TYPE = Rope.ROPE;
  STREAM: TYPE = IO.STREAM;
  UniversalFile: TYPE = AlpineEnvironment.UniversalFile;
  ByteCount: TYPE = AlpineEnvironment.ByteCount;
  ByteNumber: TYPE = ByteCount; -- index rather than count
  PageNumber: TYPE = AlpineEnvironment.PageNumber;
  bytesPerPage: CARDINAL = AlpineEnvironment.bytesPerPage;
  bytesPerWord: CARDINAL = Environment.bytesPerWord;
  wordsPerPage: CARDINAL = AlpineEnvironment.wordsPerPage;
  Data: TYPE = FileIOPrivate.Data;
  DataHandle: TYPE = REF Data;
  AlpineDataHandle: TYPE = FileIOPrivate.AlpineDataHandle;
  ProcHandle: TYPE = REF IO.StreamProcs;
  Aborted: PUBLIC ERROR [trans: REF ANY] = CODE;
  Failure: PUBLIC ERROR [what: ATOM, info: ROPE] = CODE;
  -- Stream creation
  AlpineOpen: PUBLIC PROC [
    fileName: ROPE,
    accessOptions: FileIO.AccessOptions,
    createOptions: FileIO.CreateOptions,
    closeOptions: FileIO.CloseOptions,
    transaction: REF ANY,
    raw: BOOL,
    createLength: INT,
    streamBufferParms:  FileIO.StreamBufferParms]
    RETURNS [STREAM] = TRUSTED {
    openFailure: FileIO.OpenFailure;
    { -- block for failure exit
    instance: AlpInstance.Handle;
    refUniversalFile: REF UniversalFile;
    createdFile: BOOL;
    transHandle: AlpTransaction.Handle ← NARROW[transaction !
      SafeStorage.NarrowRefFault => { openFailure ← wrongTransactionType; GOTO failure }];
    fileHandle: AlpFile.Handle;
    needRetry: BOOL ← FALSE;  haveRetried: BOOL ← FALSE;
    DO
    [instance, refUniversalFile, createdFile] ← AlpineInterimDirectory.Open[
      fileName, createOptions, createLength !
      AlpineInterimDirectory.Error =>
        SELECT why FROM
          authenticateFailed => ERROR FileIOAlpine.Failure[
            $authentication, transHandle.inst.fileStore];
          damaged, ownerRecordFull => REJECT;
          fileAlreadyExists => { openFailure ← fileAlreadyExists; GOTO failure };
          serverNotFound, ownerNotFound, fileNotFound => {
            openFailure ← fileNotFound; GOTO failure };
          illegalFileName => { openFailure ← illegalFileName; GOTO failure };
          insufficientPermission => ERROR FileIOAlpine.Failure[
            $accessDenied, transHandle.inst.fileStore];
          lockFailed, transAborted => needRetry ← TRUE;
          quota => ERROR FileIOAlpine.Failure[
            $quotaExceeded, transHandle.inst.fileStore];
          remoteCallFailed, regServersUnavailable =>
            ERROR FileIOAlpine.Failure[$communication, transHandle.inst.fileStore];
          serverBusy => ERROR FileIOAlpine.Failure[
            $serverBusy, transHandle.inst.fileStore];
          ENDCASE => REJECT];  -- DirectoryInconsistent {ownerRootFileNotFound}
        IF NOT needRetry THEN EXIT;
        IF haveRetried THEN ERROR FileIOAlpine.Failure[
          $lockConflict, transHandle.inst.fileStore];
        needRetry ← FALSE;  haveRetried ← TRUE;
      ENDLOOP;
    IF transHandle = NIL THEN transHandle ← AlpTransaction.Create[instance];
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[transHandle];
         ENDCASE => REJECT;
       RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
         $communications, transHandle.inst.fileStore];
       END;
    [fileHandle, ] ← AlpFile.Open[transHandle, refUniversalFile^,
      IF accessOptions = $read THEN $readOnly ELSE $readWrite,
      [IF accessOptions = $read THEN $read ELSE $write, $wait],
      $log, $random];
    };
    RETURN[StreamFromAlpineOpenFile[
      fileHandle, fileName, accessOptions, closeOptions, raw, streamBufferParms !
        FileIO.OpenFailed => CHECKED { openFailure ← why; GOTO failure }]];
  EXITS
    failure => {
      retryFileName: ROPE =
        SIGNAL FileIO.OpenFailed[why: openFailure, fileName: fileName];
      RETURN [AlpineOpen[retryFileName, accessOptions, createOptions, closeOptions,
        transaction, raw, createLength, streamBufferParms]]
      }
  }};--AlpineOpen
  StreamFromAlpineOpenFile: PUBLIC PROC [
    fileHandle: REF ANY,
    fileName: ROPE,
    accessOptions: FileIO.AccessOptions,
    closeOptions: FileIO.CloseOptions,
    raw: FileIO.RawOption,
    streamBufferParms:  FileIO.StreamBufferParms]
    RETURNS [stream: STREAM] = TRUSTED {
    openFailure: FileIO.OpenFailure;
    f: AlpFile.Handle = NARROW[fileHandle];
    { -- block for failure exit
    PageContainingLastByte: PROC [byteLen: INT] RETURNS [INT] = TRUSTED INLINE {
      IF byteLen = 0 THEN RETURN[0] ELSE {
        byteLen ← byteLen - 1;
        LOOPHOLE[byteLen, I.LongNumber[num]].lowbits ←
            I.BITAND[LOOPHOLE[byteLen, I.LongNumber[num]].lowbits, clearLowBits];
        RETURN[byteLen] }};
    checkForTiogaFormat: BOOL = (NOT raw) AND accessOptions # overwrite;
    byteSize: ByteCount = GetFileSize[f];
    byteLength: ByteCount = GetFileByteLength[f];
    alpineData: AlpineDataHandle ← NEW[Data.alpine ← [
      accessOptions: accessOptions,
      closeOptions: closeOptions,
      fileName: fileName,
      fileLength: byteLength,
      body: alpine[fileHandle: f, byteLength: byteLength, byteSize: byteSize]]];
    stream ← IO.CreateProcsStream[
      ProcHandleFromAccessOptions[IF checkForTiogaFormat THEN read ELSE accessOptions],
      alpineData];
    IO.StoreData[self: stream, key: $Name, data: fileName];  -- for more intelligible debugging
    IF accessOptions # read THEN SetFileByteLength[f, byteLength]; -- to change create time
    CreateBufferSpace[alpineData];
    SetupBuffer[alpineData: alpineData, fileByte: IF accessOptions = append THEN
      PageContainingLastByte[alpineData.fileLength] --get last byte of file into buffer
      ELSE 0]; --get first byte of file into buffer
    -- alpineData.index = 0 now.
    SELECT accessOptions FROM
      append => {
        -- assert alpineData.eofInBuffer (due to filePage used in SetupBuffer above).
        alpineData.index ← alpineData.dataBytesInBuffer };
      overwrite => {
        alpineData.fileLength ← 0;
        alpineData.dataBytesInBuffer ← 0;
        alpineData.eofInBuffer ← TRUE;
        };
      ENDCASE;
    IF checkForTiogaFormat THEN {
      isTioga: BOOL; len: INT;
      [yes: isTioga, len: len] ← FileIOPrivate.IsThisThingATiogaFile[stream];
      IF isTioga THEN {
        IF accessOptions = read THEN {
          -- make length look changed by sneaky call to SetLength (not in h's stream procs).
          -- since stream is opened for read only, this call won't change the length in the file.
          setLength[stream, len];
          alpineData.tiogaReader ← TRUE }
        ELSE {
          -- you can't incrementally update a Tioga file with IO!
          stream.Close[];
          openFailure ← cantUpdateTiogaFile;
          GOTO failure }
        }
      ELSE { --NOT isTioga
        -- must set procs to correct value (they were read for benefit of IsThisThingATiogaFile).
        stream.streamProcs ← ProcHandleFromAccessOptions[accessOptions];
        };
      };--checkForTiogaFormat
    RETURN[stream];
    EXITS
      failure => {
        retryFileName: ROPE =
          SIGNAL FileIO.OpenFailed[why: openFailure, fileName: fileName];
        RETURN [AlpineOpen[fileName: retryFileName, accessOptions: accessOptions,
          closeOptions: closeOptions, transaction: f.trans,
          raw: raw, streamBufferParms: streamBufferParms,
          createOptions: none, createLength: 0]]
        }
  }};--StreamFromAlpineOpenFile
  -- Get and Put
  CleanupAfterPut: PROC [selfData: DataHandle] = {
    -- Restores dataBytesInBuffer and fileLength if they are messed up by a putChar or
    --putBlock past the end of file.  Called by most stream operations not on this page.
    IF selfData.didPut THEN {
      selfData.bufferDirty ← TRUE;
      IF selfData.index > selfData.dataBytesInBuffer THEN {
        selfData.dataBytesInBuffer ← selfData.index;
        selfData.fileLength ← selfData.firstFileByteInBuffer + selfData.index };
      selfData.didPut ← FALSE }};
  getChar: PROC [self: STREAM] RETURNS [CHAR] = TRUSTED {
    selfData: DataHandle = NARROW[self.streamData];
    c: CHAR;
    IF selfData.index >= selfData.dataBytesInBuffer THEN {
      IF selfData.eofInBuffer THEN ERROR IO.EndOfStream[self];
      -- assert selfData.index = selfData.dataBytesInBuffer = selfData.bufferBytes
      AdvanceBuffer[selfData] };
    c ← LOOPHOLE[selfData.buffer[selfData.index]];
    selfData.index ← selfData.index + 1;
    RETURN[c] };
  putChar: PROC [self: STREAM, char: CHAR] = TRUSTED {
    selfData: DataHandle = NARROW[self.streamData];
    IF selfData.index = selfData.bufferBytes THEN AdvanceBuffer[selfData];
    selfData.buffer[selfData.index] ← LOOPHOLE[char];
    selfData.index ← selfData.index + 1;
    selfData.didPut ← TRUE };
  getBlock: PROC [self: STREAM, block: REF TEXT, startIndex: NAT,
    stopIndexPlusOne: NAT] RETURNS [nBytesRead: NAT] = TRUSTED {
    selfData: DataHandle = NARROW[self.streamData];
    textBlock: Environment.Block;
    countRemaining: NAT;
    -- Fail if startIndex<0 or stopIndexPlusOne<0.
    IF LOOPHOLE[I.BITOR[startIndex, stopIndexPlusOne], INTEGER] < 0 THEN
      ERROR Runtime.BoundsFault;
    -- Apply default on stopIndexPlusOne.
    stopIndexPlusOne ← MIN [block.maxLength, stopIndexPlusOne];
    textBlock ← [
      blockPointer: LOOPHOLE[block, LONG POINTER] + SIZE[TEXT[0]],
      startIndex: startIndex,
      stopIndexPlusOne: stopIndexPlusOne];
    countRemaining ←
      IF startIndex > stopIndexPlusOne THEN 0 ELSE stopIndexPlusOne-startIndex;
    nBytesRead ← 0;
    WHILE countRemaining # 0 DO
      bufferBlock: Environment.Block ← [
        blockPointer: selfData.buffer,
        startIndex: selfData.index,
        stopIndexPlusOne: selfData.dataBytesInBuffer];
      countTransferred: CARDINAL ← ByteBlt.ByteBlt[from: bufferBlock, to: textBlock];
      selfData.index ← selfData.index + countTransferred;
      nBytesRead ← nBytesRead + countTransferred;
      IF (countRemaining ← countRemaining - countTransferred) = 0 THEN EXIT;
      IF selfData.eofInBuffer THEN EXIT;
      textBlock.startIndex ← textBlock.startIndex + countTransferred;
      AdvanceBuffer[selfData];
      ENDLOOP;
    IF nBytesRead # 0 THEN block.length ← startIndex + nBytesRead;
    RETURN[nBytesRead] };
  putBlock: PROC [self: STREAM, block: REF READONLY TEXT, startIndex: NAT,
    stopIndexPlusOne: NAT] = TRUSTED {
    selfData: DataHandle = NARROW[self.streamData];
    -- Fail if startIndex<0 or stopIndexPlusOne<0.
    textBlock: Environment.Block;
    countRemaining: NAT;
    IF block = NIL THEN RETURN;
    IF LOOPHOLE[I.BITOR[startIndex, stopIndexPlusOne], INTEGER] < 0 THEN
      ERROR Runtime.BoundsFault;
    -- Apply default on stopIndexPlusOne.
    IF stopIndexPlusOne > block.maxLength THEN stopIndexPlusOne ← block.length;
    textBlock ← [
      blockPointer: LOOPHOLE[block, LONG POINTER] + SIZE[TEXT[0]],
      startIndex: startIndex,
      stopIndexPlusOne: stopIndexPlusOne];
    countRemaining ←
      IF startIndex > stopIndexPlusOne THEN 0 ELSE stopIndexPlusOne-startIndex;
    WHILE countRemaining # 0 DO
      bufferBlock: Environment.Block ← [
        blockPointer: selfData.buffer,
        startIndex: selfData.index,
        stopIndexPlusOne: selfData.bufferBytes]; -- allow put past current eof.
      countTransferred: CARDINAL ← ByteBlt.ByteBlt[from: textBlock, to: bufferBlock];
      selfData.index ← selfData.index + countTransferred;
      selfData.didPut ← TRUE;
      IF (countRemaining ← countRemaining - countTransferred) = 0 THEN EXIT;
      textBlock.startIndex ← textBlock.startIndex + countTransferred;
      AdvanceBuffer[selfData];
      ENDLOOP
    };
  maxWordsMoved: INT = (LAST[CARDINAL] / bytesPerWord) - 1;
  maxBytesMoved: INT = maxWordsMoved * bytesPerWord;
  maxStopIndexPlusOne: INT = maxBytesMoved + 1;
    -- all designed to make the max number of bytes transferred an integral number of
    --words, which is good
  unsafeGetBlock: UNSAFE PROC [self: STREAM, block: IO.UnsafeBlock]
    RETURNS [nBytesRead: INT] = UNCHECKED {
    selfData: DataHandle = NARROW[self.streamData];
    textBlock: Environment.Block;
    IF block.startIndex < 0 OR block.stopIndexPlusOne < 0 THEN ERROR IO.Error[BadIndex, self];
    IF block.startIndex >= block.stopIndexPlusOne THEN RETURN [0];
    IF block.startIndex > maxBytesMoved THEN {
      -- scale block.startIndex into [0 .. bytesPerWord)
      wordOffset: INT = block.startIndex / bytesPerWord;
      block.base ← block.base + wordOffset;
      block.startIndex ← block.startIndex - wordOffset*bytesPerWord;
      block.stopIndexPlusOne ← block.stopIndexPlusOne - wordOffset*bytesPerWord;
      };
    nBytesRead ← 0;
    DO
      -- Transfer at most maxBytesMoved bytes from the stream to block^.
      -- Assert block.startIndex IN [0 .. maxStopIndexPlusOne),  < block.stopIndexPlusOne
      countRemaining: CARDINAL;
      textBlock ← [
        blockPointer: block.base,
        startIndex: block.startIndex,
        stopIndexPlusOne: MIN[maxStopIndexPlusOne, block.stopIndexPlusOne]];
      countRemaining ← textBlock.stopIndexPlusOne - textBlock.startIndex;
      -- Assert countRemaining > 0
      -- The following loop transfers from the stream to textBlock^ until textBlock^ is full
      --or end of file is reached.
      DO
        bufferBlock: Environment.Block ← [
          blockPointer: selfData.buffer,
          startIndex: selfData.index,
          stopIndexPlusOne: selfData.dataBytesInBuffer];
        countTransferred: CARDINAL ← ByteBlt.ByteBlt[from: bufferBlock, to: textBlock];
        selfData.index ← selfData.index + countTransferred;
        nBytesRead ← nBytesRead + countTransferred;
        IF (countRemaining ← countRemaining - countTransferred) = 0 THEN EXIT;
        IF selfData.eofInBuffer THEN GOTO return;
        textBlock.startIndex ← textBlock.startIndex + countTransferred;
        AdvanceBuffer[selfData];
        ENDLOOP;
      IF textBlock.stopIndexPlusOne = block.stopIndexPlusOne THEN GOTO return;
      -- Assert textBlock.stopIndexPlusOne = maxStopIndexPlusOne
      block.base ← block.base + maxWordsMoved;
      block.startIndex ← 0;
      block.stopIndexPlusOne ← block.stopIndexPlusOne - maxBytesMoved;
      ENDLOOP;
    EXITS
      return => RETURN [nBytesRead]
    };
  unsafePutBlock: PROC [self: STREAM, block: IO.UnsafeBlock] = TRUSTED {
    selfData: DataHandle = NARROW[self.streamData];
    textBlock: Environment.Block;
    IF block.startIndex < 0 OR block.stopIndexPlusOne < 0 THEN ERROR IO.Error[BadIndex, self];
    IF block.startIndex >= block.stopIndexPlusOne THEN RETURN;
    IF block.startIndex > maxBytesMoved THEN {
      -- scale block.startIndex into [0 .. bytesPerWord)
      wordOffset: INT = block.startIndex / bytesPerWord;
      block.base ← block.base + wordOffset;
      block.startIndex ← block.startIndex - wordOffset*bytesPerWord;
      block.stopIndexPlusOne ← block.stopIndexPlusOne - wordOffset*bytesPerWord;
      };
    DO
      -- Transfer at most maxBytesMoved bytes from block^ to the stream.
      -- Assert block.startIndex IN [0 .. maxStopIndexPlusOne),  < block.stopIndexPlusOne
      countRemaining: CARDINAL;
      textBlock ← [
        blockPointer: block.base,
        startIndex: block.startIndex,
        stopIndexPlusOne: MIN[maxStopIndexPlusOne, block.stopIndexPlusOne]];
      countRemaining ← textBlock.stopIndexPlusOne - textBlock.startIndex;
      -- Assert countRemaining > 0
      -- The following loop transfers textBlock^ to the stream.
      DO
        bufferBlock: Environment.Block ← [
          blockPointer: selfData.buffer,
          startIndex: selfData.index,
          stopIndexPlusOne: selfData.bufferBytes]; -- allow put past current eof.
        countTransferred: CARDINAL ← ByteBlt.ByteBlt[from: textBlock, to: bufferBlock];
        selfData.index ← selfData.index + countTransferred;
        selfData.didPut ← TRUE;
        IF (countRemaining ← countRemaining - countTransferred) = 0 THEN EXIT;
        textBlock.startIndex ← textBlock.startIndex + countTransferred;
        AdvanceBuffer[selfData];
        ENDLOOP;
      IF textBlock.stopIndexPlusOne = block.stopIndexPlusOne THEN EXIT;
      -- Assert textBlock.stopIndexPlusOne = maxStopIndexPlusOne
      block.base ← block.base + maxWordsMoved;
      block.startIndex ← 0;
      block.stopIndexPlusOne ← block.stopIndexPlusOne - maxBytesMoved;
      ENDLOOP
    };
  AdvanceBuffer: PROC [selfData: DataHandle] = TRUSTED {
    -- On entry, index = dataBytesInBuffer = bufferBytes.  Exit with same position in
    --file, but index < dataBytesInBuffer or EOF.
    -- Handles implicit file extension.
    -- Called from getChar, putChar, getBlock, putBlock.
    alpineData: AlpineDataHandle = NARROW[selfData];
    firstByteOfNextPage: INT = alpineData.firstFileByteInBuffer + alpineData.bufferBytes;
    changeSize: BOOL ← FALSE;
    IF firstByteOfNextPage = maxLength THEN ERROR IO.Error[FileTooLong, NIL];
    CleanupAfterPut[alpineData];
    IF firstByteOfNextPage >= alpineData.byteSize THEN {
      alpineData.byteSize ← NewByteSize[alpineData.byteSize];
      SetFileSize[alpineData.fileHandle, alpineData.byteSize] };
    SetupBuffer[alpineData: alpineData, fileByte: firstByteOfNextPage];
    alpineData.index ← I.LowHalf[firstByteOfNextPage-alpineData.firstFileByteInBuffer];
    };
  NewByteSize: PROC [byteCount: ByteCount] RETURNS [ByteCount] = {
    RETURN [byteCount+5120];
    };
  endOf: PROC [self: STREAM]  RETURNS[BOOL] = {
    -- Requires no CleanupAfterPut.
    selfData: DataHandle = NARROW[self.streamData];
    RETURN[selfData.eofInBuffer AND selfData.index >= selfData.dataBytesInBuffer] };
  charsAvail: PROC [self: STREAM] RETURNS [BOOL] = {
    RETURN[TRUE] };
  getIndex: PROC [self: STREAM] RETURNS [INT] = {
    -- Requires no CleanupAfterPut.
    selfData: DataHandle = NARROW[self.streamData];
    RETURN[selfData.firstFileByteInBuffer + selfData.index] };
  setIndex: PROC [self: STREAM, index: INT] = TRUSTED {
    firstByte: INT ← index;
    byte: CARDINAL; --will contain index - firstByte
    alpineData: AlpineDataHandle = NARROW[self.streamData];
    firstBufferByte: INT = alpineData.firstFileByteInBuffer;
    newIndex: CARDINAL;
    IF index < 0 THEN ERROR IO.Error[BadIndex, self];
    LOOPHOLE[firstByte, I.LongNumber[num]].lowbits ←
          I.BITAND[LOOPHOLE[firstByte, I.LongNumber[num]].lowbits, clearLowBits];
    -- firstByte contains index of first byte of file page containing byte "index"
    byte ← I.BITAND[LOOPHOLE[index, I.LongNumber[num]].lowbits, clearHighBits];
    -- byte contains index - firstByte
    IF alpineData.didPut THEN { -- CleanupAfterPut[alpineData]
      alpineData.bufferDirty ← TRUE;
      IF alpineData.index > alpineData.dataBytesInBuffer THEN {
        alpineData.dataBytesInBuffer ← alpineData.index;
        alpineData.fileLength ← alpineData.firstFileByteInBuffer + alpineData.index };
      alpineData.didPut ← FALSE };
    -- ensure that page containing byte "index" is in the buffer
    IF firstByte NOT IN [firstBufferByte .. firstBufferByte+alpineData.bufferBytes) THEN {
      IF index > alpineData.fileLength THEN ERROR IO.EndOfStream[self];
      IF alpineData.byteSize < firstBufferByte+alpineData.dataBytesInBuffer THEN {
        -- Analogous to AdvanceBuffer (bytes in buffer are not covered by file, but this
        --time we may be jumping away from the EOF.)
        alpineData.byteSize ← NewByteSize[alpineData.byteSize];
        SetFileSize[alpineData.fileHandle, alpineData.byteSize] };
      SetupBuffer[alpineData: alpineData, fileByte: firstByte];
      };
    newIndex ← I.LowHalf[firstByte-alpineData.firstFileByteInBuffer] + byte;
    IF newIndex > alpineData.dataBytesInBuffer THEN ERROR IO.EndOfStream[self];
    alpineData.index ← newIndex };
  reset: PROC [self: STREAM] = {
    setIndex[self, getLength[self]] };
  flush: PROC [self: STREAM] = TRUSTED {
    alpineData: AlpineDataHandle = NARROW[self.streamData];
    commitAndReopenTrans: BOOL =
      I.BITAND[alpineData.closeOptions, FileIO.commitAndReopenTransOnFlush] # 0;
    ForceOut[alpineData, IF commitAndReopenTrans THEN $continue ELSE $none, FALSE];
    };
  close: PROC [self: STREAM, abort: BOOL] = TRUSTED {
    alpineData: AlpineDataHandle = NARROW[self.streamData];
    finishTrans: BOOL =
      I.BITAND[alpineData.closeOptions, FileIO.finishTransOnClose] # 0;
    ForceOut[alpineData, IF finishTrans THEN $complete ELSE $none, abort];
    DeleteBufferSpace[alpineData];
    alpineData.streamIsClosed ← TRUE;
    FileIOPrivate.Invalidate[self] };
  -- Procs that are called via the property list mechanism.
  getLength: PROC [self: STREAM] RETURNS [length: INT] = {
    selfData: DataHandle = NARROW[self.streamData];
    IF selfData.streamIsClosed THEN ERROR IO.Error[StreamClosed, self];
    -- special CleanupAfterPut[selfData]; just clean up file length,
    --let some later call do the rest
    IF selfData.didPut AND selfData.index > selfData.dataBytesInBuffer THEN {
      selfData.fileLength ← selfData.firstFileByteInBuffer + selfData.index };
    RETURN[selfData.fileLength] };
  clearLowBits: CARDINAL = CARDINAL.LAST-(bytesPerPage-1);
  clearHighBits: CARDINAL = (bytesPerPage-1);
  maxLength: INT = INT.LAST - bytesPerPage;
  setLength: PROC [self: STREAM, length: INT] = TRUSTED {
    -- Note: do not reduce the size of a shortened file until stream closed.
    RoundUpToPages: PROC [bytes: INT] RETURNS [INT] = TRUSTED INLINE {
      bytes ← bytes + (bytesPerPage-1);
      LOOPHOLE[bytes, I.LongNumber[num]].lowbits ←
        I.BITAND[LOOPHOLE[bytes, I.LongNumber[num]].lowbits, clearLowBits];
      RETURN[bytes] };
    alpineData: AlpineDataHandle = NARROW[self.streamData];
    newFileBytes, firstBufferByte: INT;
    IF alpineData.streamIsClosed THEN ERROR IO.Error[StreamClosed, self];
    IF length NOT IN [0 .. maxLength] THEN ERROR IO.Error[BadIndex, self];
    newFileBytes ← RoundUpToPages[length];
    IF alpineData.didPut THEN { -- CleanupAfterPut[alpineData]
      alpineData.bufferDirty ← TRUE;
      alpineData.didPut ← FALSE };
    firstBufferByte ← alpineData.firstFileByteInBuffer;
    alpineData.fileLength ← length;
    SELECT TRUE FROM
      length > firstBufferByte + alpineData.bufferBytes => {
        -- new last byte of file is past end of current buffer.
        IF length > alpineData.byteSize THEN { --extend file to newFileBytes now
          alpineData.byteSize ← newFileBytes;
          SetFileSize[alpineData.fileHandle, alpineData.byteSize] };
        alpineData.dataBytesInBuffer ← alpineData.bufferBytes;
        alpineData.eofInBuffer ← FALSE };
      length > firstBufferByte OR (length = 0 AND firstBufferByte = 0) => {
        -- new last byte of file is in current buffer, or new file is empty and
        --first data page is first page of buffer.  Defer actually changing file length;
        --this is analogous to extending file with puts.
        alpineData.eofInBuffer ← TRUE;
        alpineData.dataBytesInBuffer ← length - firstBufferByte;
        alpineData.index ← MIN[alpineData.index, alpineData.dataBytesInBuffer] };
      ENDCASE => {
        -- last byte of file precedes current buffer. (a special case of this, length
        --= 0 and firstBufferByte = 0, was already handled above without a
        --SetupBuffer call).
        alpineData.bufferDirty ← FALSE; --avoid redundant write if buffer dirty.
        SetupBuffer[alpineData: alpineData, fileByte: newFileBytes-bytesPerPage];
        alpineData.index ← alpineData.dataBytesInBuffer };
    };
  eraseChar: PROC [self: STREAM, char: CHAR] = {
    index: INT = getIndex[self];
    IF index = 0 THEN ERROR IO.Error[IllegalBackup, self];
    setIndex[self, index-1];
    IF getChar[self] # char THEN {putChar[self, '\\]; putChar[self, char]}
    ELSE setIndex[self, index-1] };
    
  backup: PROC [self: STREAM, char: CHAR] = {
    selfData: DataHandle = NARROW[self.streamData];
    index: INT;
    IF selfData.streamIsClosed THEN ERROR IO.Error[StreamClosed, self];
    index ←  getIndex[self];
    IF index = 0 THEN ERROR IO.Error[IllegalBackup, self];
    setIndex[self, index-1];
    IF getChar[self] # char THEN ERROR IO.Error[IllegalBackup, self];
    setIndex[self, index-1] };
  -- Buffer management
  growIncrement: CARDINAL = 4; --if we ever need to grow file, we grow it by this many pages.
  growIncrementBytes: CARDINAL = growIncrement*bytesPerPage;
  CreateBufferSpace: PROC [alpineData: AlpineDataHandle] = TRUSTED {
    alpineData.bufferSpace ← Space.Create[1, Space.virtualMemory];
    Space.Map[alpineData.bufferSpace];
    alpineData.buffer ← Space.LongPointer[alpineData.bufferSpace];
    alpineData.bufferBytes ← bytesPerPage };
  DeleteBufferSpace: PROC [alpineData: AlpineDataHandle] = TRUSTED {
    Space.Delete[alpineData.bufferSpace];
    alpineData.buffer ← NIL };
  SetupBuffer: PROC [alpineData: AlpineDataHandle, fileByte: INT] = TRUSTED {
    -- didPut = FALSE on entry (someone else called CleanupAfterPut).
    -- Arranges buffer so that fileByte (must be page-aligned) is the first byte in it.
    -- If buffer is dirty, writes it to file (file page has already been allocated).
    -- Maintains invariants of eofInBuffer, dataBytesInBuffer, bufferBytes, and
    --firstFileByteInBuffer in the face of all this.  DOES NOT update index.
    -- Called from StreamFromAlpineOpenFile, AdvanceBuffer, setLength, setIndex.
    bytesToRead: CARDINAL;
    IF alpineData.bufferDirty THEN {
      WriteFilePage[f: alpineData.fileHandle,
        to: alpineData.firstFileByteInBuffer, from: alpineData.buffer];
      alpineData.bufferDirty ← FALSE };
    IF (bytesToRead ← I.LowHalf[MIN[alpineData.fileLength - fileByte, bytesPerPage]]) > 0 THEN
      ReadFilePage[f: alpineData.fileHandle, from: fileByte, to: alpineData.buffer];
    alpineData.firstFileByteInBuffer ← fileByte;
    alpineData.eofInBuffer ← alpineData.fileLength <= (fileByte + bytesPerPage);
    alpineData.dataBytesInBuffer ← bytesToRead };
  ForceOut: PROC [alpineData: AlpineDataHandle,
    commitAction: {none, complete, continue}, abort: BOOL] = TRUSTED {
    -- Called from Flush, Close.
    -- This is the only proc that sets byte length, and only proc that finishes trans.
    CleanupAfterPut[alpineData];
    IF alpineData.bufferDirty THEN {
      WriteFilePage[f: alpineData.fileHandle,
        to: alpineData.firstFileByteInBuffer, from: alpineData.buffer];
      alpineData.bufferDirty ← FALSE };
    IF alpineData.fileLength # alpineData.byteLength AND NOT alpineData.tiogaReader THEN {
      alpineData.byteLength ← alpineData.fileLength;
      SetFileByteLength[alpineData.fileHandle, alpineData.byteLength] };
    IF commitAction # $none THEN Finish[
      f: alpineData.fileHandle,
      requestedOutcome: IF abort THEN $abort ELSE $commit,
      continue: commitAction = $continue];
    };
  -- Talking to Alpine (catch phrases galore ... )
  ReadFilePage: PROC [f: REF ANY, from: ByteNumber, to: LONG POINTER] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    p: PageNumber = from/bytesPerPage;
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    fileHandle.ReadPages[
      pageRun: [firstPage: p],
      pageBuffer: DESCRIPTOR [to, wordsPerPage]];
    }};
  WriteFilePage: PROC [f: REF ANY, to: ByteNumber, from: LONG POINTER] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    p: PageNumber = to/bytesPerPage;
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    fileHandle.WritePages[
      pageRun: [firstPage: p],
      pageBuffer: DESCRIPTOR [from, wordsPerPage]];
    }};
  SetFileSize: PROC [f: REF ANY, byteSize: ByteCount] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    fileHandle.SetSize[byteSize/bytesPerPage];
    }};
  GetFileSize: PROC [f: REF ANY] RETURNS [ByteCount] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    RETURN [fileHandle.GetSize[]*bytesPerPage];
    }};
  SetFileByteLength: PROC [f: REF ANY, byteLength: ByteCount] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    now: System.GreenwichMeanTime = System.GetGreenwichMeanTime[];
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    fileHandle.WriteProperties[properties:
      LIST[[byteLength[byteLength: byteLength]], [createTime[createTime: now]]]];
    }};
  GetFileByteLength: PROC [f: REF ANY] RETURNS [ByteCount] = TRUSTED {
    fileHandle: AlpFile.Handle = NARROW[f];
    { ENABLE BEGIN
      AlpFile.Unknown => SELECT what FROM
        transID, openFileID => ERROR FileIOAlpine.Aborted[fileHandle.trans];
        ENDCASE => REJECT;
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    byteLengthProperty: LIST OF AlpineEnvironment.PropertyValuePair =
      fileHandle.ReadProperties[[byteLength: TRUE]];
    RETURN [NARROW[byteLengthProperty.first,
       AlpineEnvironment.PropertyValuePair.byteLength].byteLength];
    }};
  Finish: PROC [f: REF ANY,
    requestedOutcome: AlpineEnvironment.CommitOrAbort, continue: BOOL] = {
    fileHandle: AlpFile.Handle = NARROW[f];
    { ENABLE BEGIN
      RPC.CallFailed => IF why IN [timeout .. busy] THEN ERROR FileIOAlpine.Failure[
        $communications, fileHandle.trans.inst.fileStore];
      END;
    outcome: AlpineEnvironment.Outcome = fileHandle.trans.Finish[
      requestedOutcome: requestedOutcome, continue: continue];
    IF NOT (requestedOutcome = $abort) AND outcome = $abort THEN
      ERROR FileIOAlpine.Aborted[fileHandle.trans];
    }};
  -- Procedure records (never modified)
  alpineFileIOReadProcs: ProcHandle = IO.CreateRefStreamProcs[
    getChar:  getChar,
    endOf: endOf,
    charsAvail: charsAvail,
    getBlock: getBlock,
    unsafeGetBlock: unsafeGetBlock,
    
    putChar: FileIOPrivate.PutCharDisallowed,
    putBlock:  FileIOPrivate.PutBlockDisallowed,
    unsafePutBlock: FileIOPrivate.UnsafePutBlockDisallowed,
    flush: flush,
    
    reset: reset,
    close: close,
    getIndex: getIndex,
    setIndex: setIndex,
    
    backup: backup,
    getLength: getLength,
    
    name: "ReadOnly Alpine File"
    ];
  alpineFileIOAppendProcs: ProcHandle = IO.CreateRefStreamProcs[
    getChar:  FileIOPrivate.GetCharDisallowed,
    endOf: endOf,
    charsAvail: charsAvail,
    getBlock: FileIOPrivate.GetBlockDisallowed,
    unsafeGetBlock: FileIOPrivate.UnsafeGetBlockDisallowed,
    
    putChar: putChar,
    putBlock:  putBlock,
    unsafePutBlock: unsafePutBlock,
    flush: flush,
    
    reset: reset,
    close: close,
    getIndex: getIndex,
    setIndex: FileIOPrivate.SetIndexDisallowed,
    
    getLength: getLength,
    
    name: "AppendOnly Alpine File"
    ];
  alpineFileIOAllProcs: ProcHandle = IO.CreateRefStreamProcs[
    getChar:  getChar,
    endOf: endOf,
    charsAvail: charsAvail,
    getBlock: getBlock,
    unsafeGetBlock: unsafeGetBlock,
    
    putChar: putChar,
    putBlock:  putBlock,
    unsafePutBlock: unsafePutBlock,
    flush: flush,
    
    reset: reset,
    close: close,
    getIndex: getIndex,
    setIndex: setIndex,
    
    backup: backup,
    getLength: getLength,
    setLength: setLength,
    
    name: "Read/Write Alpine File"
    ];
  ProcHandleFromAccessOptions: ARRAY FileIO.AccessOptions OF ProcHandle = [
    read: alpineFileIOReadProcs,
    append: alpineFileIOAppendProcs,
    write: alpineFileIOAllProcs,
    overwrite: alpineFileIOAllProcs];
END.
CHANGE LOG
Created by MBrown on May 10, 1983 8:36 pm
-- By editing FileIOJuniperImpl
Changed by MBrown on June 3, 1983 4:46 pm
-- Change create time of non-readonly file on Open, and whenever byte length changes.