-- FTPPilotFile.mesa
--  Edit: HGM, February 27, 1981  2:46 PM  Fix for doubling create date
--  Edit: HGM, February 4, 1981  11:19 AM
--  Edit: BLyon, August 26, 1980  4:04 PM

DIRECTORY
  DCSFileTypes USING [tLeaderPage],
  Directory USING [
    CreateFile, CreateSystemDirectory,
    DeleteFile, Error, Handle, GetNext, GetProperty, LookupUnlimited],
  Environment USING [bytesPerPage, bytesPerWord, wordsPerPage],
  File USING [
    Capability, delete, Error, GetAttributes, grow, LimitPermissions,
    nullCapability, PageCount, Permissions, read, shrink, Type,
    write],
  FileStream USING [
    Create, GetLeaderProperties, GetLeaderPropertiesForCapability, GetLength,
    GetIndex, IndexOutOfRange, NoLeaderPage, SetLeaderProperties, SetLength,
    SetIndex, Subtype],
  FTPDefs,
  FTPPrivateDefs,
  Inline USING [BITOR, LowHalf],
  PropertyTypes USING [tFileName],
  Space USING [Create, Delete, Handle, Map, mds, Pointer, Unmap],
  Stream USING [Block, CompletionCode, Delete, Handle, GetBlock, PutBlock],
  String USING [
    AppendChar, AppendLongNumber, AppendString, AppendSubString, EquivalentString,
    SubStringDescriptor],
  System USING [gmtEpoch, GreenwichMeanTime],
  Storage USING [Node, Free],
  Time USING [Append, Invalid, Unpack],
  TimeExtra USING [PackedTimeFromString],
  Volume USING [ID, systemID, InsufficientSpace];

FTPPilotFile: MONITOR
  IMPORTS
    Directory, File, FileStream, Inline, Space, Stream, String, Storage, Time,
    TimeExtra, Volume, FTPPrivateDefs
  EXPORTS FTPDefs
  SHARES FTPDefs, FTPPrivateDefs =
  BEGIN OPEN FTPDefs, FTPPrivateDefs;

  -- Note:  Absolute filenames should have format as specified by Pilot Directories.

  -- **********************!  Types  !***********************

  -- pilot file system state information
  PilotFileSystem: TYPE = POINTER TO PilotFileSystemObject;
  PilotFileSystemObject: TYPE = RECORD [bufferSize: CARDINAL];

  -- pilot file handle state information
  PilotFileHandle: TYPE = POINTER TO PilotFileHandleObject;
  PilotFileHandleObject: TYPE = RECORD [
    mode: Mode, fileCapability: File.Capability, streamHandle: Stream.Handle];

  -- **********************!  Constants  !***********************

  defaultBufferSize: CARDINAL = 4; -- in pages

  bytesPerPage: CARDINAL = Environment.bytesPerPage;
  bytesPerWord: CARDINAL = Environment.bytesPerWord;
  wordsPerPage: CARDINAL = Environment.wordsPerPage;

  filenameWildString: CHARACTER = '*;
  filenameWildCharacter: CHARACTER = '#;
  filenameNameVersionSeparator: CHARACTER = '!;

  ftpsystem: POINTER TO FTPSystem = LocateFtpSystemObject[];

  filePrimitivesObject: FilePrimitivesObject ←
    [CreateFileSystem: CreateFileSystem, DestroyFileSystem: DestroyFileSystem,
      DecomposeFilename: DecomposeFilename, ComposeFilename: ComposeFilename,
      InspectCredentials: InspectCredentials, EnumerateFiles: EnumerateFiles,
      OpenFile: OpenFile, ReadFile: ReadFile, WriteFile: WriteFile,
      CloseFile: CloseFile, DeleteFile: DeleteFile, RenameFile: RenameFile];

  -- **********************!  Variables  !***********************


  uniqueFileTag: LONG INTEGER ← 0;

  -- **********************!  File Foothold Procedure  !***********************

  PilotFilePrimitives, SomeFilePrimitives: PUBLIC PROCEDURE
    RETURNS [filePrimitives: FilePrimitives] =
    BEGIN
    -- return file primitives
    RETURN[@filePrimitivesObject];
    END;

  -- **********************!  File Primitives  !***********************

  CreateFileSystem: PROCEDURE [bufferSize: CARDINAL]
    RETURNS [fileSystem: FileSystem] =
    BEGIN
    -- Note:  bufferSize expressed in pages; zero implies default.
    -- allocate and initialize file system object
    pilotFS: PilotFileSystem ← Storage.Node[SIZE[PilotFileSystemObject]];
    pilotFS.bufferSize ← IF bufferSize # 0 THEN bufferSize ELSE defaultBufferSize;
    RETURN[LOOPHOLE[pilotFS, FileSystem]];
    END;

  DestroyFileSystem: PROCEDURE [fileSystem: FileSystem] =
    BEGIN
    -- release file system object
    Storage.Free[LOOPHOLE[fileSystem, PilotFileSystem]];
    END;

  DecomposeFilename: PROCEDURE [
    fileSystem: FileSystem, absoluteFilename: STRING,
    virtualFilename: VirtualFilename] =
    BEGIN OPEN virtualFilename;
    -- Note:  Absolute filenames have the following syntax,
    -- with name non-empty and version non-empty and numeric:
    --     name [filenameNameVersionSeparator version]
    -- We accept file names with version numbers even though the Pilot Directory doesn't
    -- have this feature.
    -- Virtual filename components are never NIL, they
    -- supply empty device and directory components if necessary.
    i: CARDINAL;
    character: CHARACTER;
    field: STRING ← name;
    -- initialize virtual filename components to empty
    device.length ← directory.length ← name.length ← version.length ← 0;
    -- process each character in absolute filename
    FOR i IN [0..absoluteFilename.length) DO
      -- select character
      character ← absoluteFilename[i];
      -- switch to version if character is name-version separator
      IF field = name AND character = filenameNameVersionSeparator THEN
        field ← version
        -- append character to name or version as appropriate

      ELSE
        BEGIN
        IF field = version AND character NOT IN ['0..'9] THEN Abort[illegalFilename];
        String.AppendChar[field, character];
        END;
      ENDLOOP;
    -- abort if either name or version is empty
    IF name.length = 0 OR (field = version AND version.length = 0) THEN
      Abort[illegalFilename];
    END;

  ComposeFilename: PROCEDURE [
    fileSystem: FileSystem, absoluteFilename: STRING,
    virtualFilename: VirtualFilename] =
    BEGIN OPEN virtualFilename;
    -- Note:  Absolute filenames have the following syntax,
    -- with name non-empty and version non-empty and numeric:
    --     name [filenameNameVersionSeparator version].
    -- We accept file names with version numbers even though the Pilot Directory doesn't
    -- have this feature.
    -- Virtual filename components are never NIL;
    -- ignores device and directory components;
    -- uses name and version components as defaults.
    -- local constants
    explicitDevice: STRING = [0];
    explicitDirectory: STRING = [0];
    -- local variables
    explicitName: STRING ← [maxStringLength];
    explicitVersion: STRING ← [maxStringLength];
    explicitVirtualFilenameObject: VirtualFilenameObject ←
      [device: explicitDevice, directory: explicitDirectory, name: explicitName,
        version: explicitVersion];
    i: CARDINAL;
    -- return at once if absolute filename is all there is
    IF name.length = 0 AND version.length = 0 THEN RETURN;
    -- decompose absolute filename
    IF absoluteFilename.length # 0 THEN
      DecomposeFilename[
        fileSystem, absoluteFilename, @explicitVirtualFilenameObject];
    -- apply defaults as necessary
    IF explicitName.length = 0 THEN explicitName ← name;
    IF explicitVersion.length = 0 THEN explicitVersion ← version;
    -- initialize absolute filename to empty
    absoluteFilename.length ← 0;
    -- output name always
    IF explicitName.length = 0 THEN Abort[illegalFilename];
    String.AppendString[absoluteFilename, explicitName];
    -- output version if specified
    IF explicitVersion.length # 0 THEN
      BEGIN
      -- verify that version is numeric
      FOR i IN [0..explicitVersion.length) DO
        IF explicitVersion[i] NOT IN ['0..'9] THEN Abort[illegalFilename]; ENDLOOP;
      -- output name-version separator
      String.AppendChar[absoluteFilename, filenameNameVersionSeparator];
      -- output version
      String.AppendString[absoluteFilename, explicitVersion];
      END;
    END;

  InspectCredentials: ENTRY PROCEDURE [
    fileSystem: FileSystem, status: Status, user, password: STRING] =
    BEGIN
    -- no operation

    END;

  EnumerateFiles: PROCEDURE [
    fileSystem: FileSystem, files: STRING, intent: EnumerateFilesIntent,
    processFile: PROCEDURE [UNSPECIFIED, STRING, FileInfo],
    processFileData: UNSPECIFIED] =
    BEGIN
    -- Note:  Implements filenameWildString and filenameWildCharacter;
    --   skips directory search if none of either present; supplies no file information (not true for this, Tajo's own, version).

    -- MaskFilename procedure
    MaskFilename: PROCEDURE [
      file: STRING, fileIndex: CARDINAL, mask: STRING, maskIndex: CARDINAL]
      RETURNS [outcome: BOOLEAN] =
      BEGIN
      -- local variables
      i, j: CARDINAL;
      -- process each character in mask
      FOR i IN [maskIndex..mask.length) DO
        SELECT mask[i] FROM
          filenameWildString => -- matches any string of zero or more characters
            BEGIN
            FOR j IN [fileIndex..file.length] DO
              IF MaskFilename[file, j, mask, i + 1] THEN RETURN[TRUE]; ENDLOOP;
            RETURN[FALSE];
            END;
          filenameWildCharacter => -- matches any single character
            IF fileIndex = file.length THEN RETURN[FALSE]
            ELSE fileIndex ← fileIndex + 1;
          ENDCASE => -- matches itself (ignoring case differences)
            IF fileIndex = file.length OR Inline.BITOR[
              LOOPHOLE[file[fileIndex], UNSPECIFIED], 40B] # Inline.BITOR[
              LOOPHOLE[mask[i], UNSPECIFIED], 40B] THEN RETURN[FALSE]
            ELSE fileIndex ← fileIndex + 1;
        ENDLOOP;
      -- filename passes mask if entire filename has been consumed
      outcome ← fileIndex = file.length;
      END;

    -- local variables
    split: String.SubStringDescriptor;
    splitName: STRING ← [maxStringLength];
    cap: File.Capability;
    name: STRING ← [maxStringLength];
    cStr: STRING ← [maxStringLength];
    wStr: STRING ← [maxStringLength];
    rStr: STRING ← [maxStringLength];
    fileInfoObject: FileInfoObject ←
      [fileType: unknown, byteSize: 8, byteCount: 0, creationDate: cStr,
        writeDate: wStr, readDate: rStr, author: NIL];

    FillInfo: PROCEDURE =
      BEGIN OPEN fileInfoObject, Time;
      cDate, wDate, rDate: System.GreenwichMeanTime ← System.gmtEpoch;
      subType: FileStream.Subtype ← null;
      creationDate.length ← writeDate.length ← readDate.length ← 0;
      [type: subType, create: cDate, write: wDate, read: rDate, length: byteCount]
        ← FileStream.GetLeaderPropertiesForCapability[
        cap ! FileStream.NoLeaderPage => CONTINUE];
      fileType ←
        SELECT subType FROM
          text => text,
          byteBinary, wordBinary => binary,
          ENDCASE => unknown;
      Append[s: creationDate, unpacked: Unpack[cDate] ! Invalid => CONTINUE];
      Append[s: writeDate, unpacked: Unpack[wDate] ! Invalid => CONTINUE];
      Append[s: readDate, unpacked: Unpack[rDate] ! Invalid => CONTINUE];
      END;

    name.length ← 0;
    DO
      cap ← Directory.GetNext["WorkDir>*"L, name, name];
      IF name.length = 0 THEN EXIT;
      -- no terminating period
      -- output file if it satisfies the mask
      -- As a temporary hack, directory qualification is discarded!
      split ← [base: name, length:, offset:];
      FOR i: CARDINAL DECREASING IN [0..name.length) DO
        IF name[i] = '> THEN {split.offset ← i + 1; EXIT}; ENDLOOP;
      split.length ← name.length - split.offset;
      splitName.length ← 0;
      String.AppendSubString[splitName, @split];
      IF MaskFilename[splitName, 0, files, 0] THEN {
        FillInfo[]; processFile[processFileData, splitName, @fileInfoObject]};
      ENDLOOP;
    END;

  OpenFile: ENTRY PROCEDURE [
    fileSystem: FileSystem, file: STRING, mode: Mode, fileTypePlease: BOOLEAN,
    info: FileInfo] RETURNS [fileHandle: FileHandle, fileType: FileType] =
    BEGIN
    ENABLE UNWIND => NULL;
    -- Note:  Supplies scratch filename if file.length=0.
    -- local constants
    existingFileRequired: BOOLEAN =
      (mode = read OR mode = append OR mode = readThenWrite);
    permissions: File.Permissions =
      SELECT mode FROM
        read => File.read,
        append => File.read + File.write + File.grow + File.shrink,
        ENDCASE => File.read + File.write + File.grow + File.shrink + File.delete;
    -- write, writeThenRead, readThenWrite
    -- local variables
    successful: BOOLEAN;
    cap: File.Capability ← File.nullCapability;
    pilotFileType: File.Type;
    goodInitialFileSize: File.PageCount = 100;
    pilotFH: PilotFileHandle ← NIL;
    fileSubtype: FileStream.Subtype;
    leaderFileName: STRING ← [maxStringLength];
    createDate: System.GreenwichMeanTime;
    -- generate unique scratch filename if necessary
    IF file.length = 0 THEN
      BEGIN
      String.AppendString[file, "FTPPilotFile-"L];
      String.AppendLongNumber[file, UniqueFileTag[], 10];
      String.AppendString[file, ".Scratch"L];
      END;
    -- catch erorrs
    BEGIN
    ENABLE
      BEGIN
      UNWIND => BEGIN IF pilotFH # NIL THEN Storage.Free[pilotFH]; END;
      Directory.Error =>
        IF type = invalidFileName THEN
          AbortWithExplanation[requestedAccessDenied, file];
      END;
    -- find this file in the directory
    successful ← TRUE;
    cap ← Directory.LookupUnlimited[
      fileName: file !
      Directory.Error =>
        IF type = fileNotFound THEN {successful ← FALSE; CONTINUE}];
    IF NOT successful THEN
      BEGIN
      IF existingFileRequired THEN Abort[noSuchFile]
      ELSE
        BEGIN
        cap ← Directory.CreateFile[file, DCSFileTypes.tLeaderPage, goodInitialFileSize];
        END;
      END;
    -- initialize pilot file handle object
    pilotFH ← Storage.Node[SIZE[PilotFileHandleObject]];
    fileHandle ← LOOPHOLE[pilotFH, FileHandle];
    pilotFH.mode ← mode;
    pilotFH.fileCapability ← File.LimitPermissions[cap, permissions];
    pilotFH.streamHandle ← FileStream.Create[pilotFH.fileCapability];
    [pilotFileType, , , ] ← File.GetAttributes[pilotFH.fileCapability];
    IF pilotFileType = DCSFileTypes.tLeaderPage THEN
      [type: fileSubtype, create: createDate] ← FileStream.GetLeaderProperties[
        pilotFH.streamHandle, leaderFileName];
    -- determine file type if necessary
    fileType ←
      SELECT TRUE FROM
        ~fileTypePlease OR pilotFileType # DCSFileTypes.tLeaderPage => unknown,
        fileSubtype = text => text,
        fileSubtype = byteBinary => binary,
        ENDCASE => unknown;
    -- process the info
    IF info # NIL THEN
      BEGIN
      IF mode = write AND info.creationDate # NIL AND pilotFileType =
        DCSFileTypes.tLeaderPage THEN
        FileStream.SetLeaderProperties[
          sH: pilotFH.streamHandle,
          create: TimeExtra.PackedTimeFromString[info.creationDate]];
      IF (mode = read OR mode = readThenWrite) AND info.creationDate # NIL
      AND info.creationDate.length = 0  -- Filled in by Enumerate
      AND pilotFileType = DCSFileTypes.tLeaderPage THEN
        Time.Append[info.creationDate, Time.Unpack[createDate]];
      END;
    END; -- enable

    END;

  -- This procedure reads the entire contents of a file when it is called.

  ReadFile: ENTRY PROCEDURE [
    fileSystem: FileSystem, fileHandle: FileHandle,
    sendBlock: PROCEDURE [UNSPECIFIED, POINTER, CARDINAL],
    sendBlockData: UNSPECIFIED] =
    BEGIN OPEN pilotFH: LOOPHOLE[fileHandle, PilotFileHandle];
    ENABLE UNWIND => NULL;
    -- Note:  Assumes invocation is consistent with mode declared via OpenFile.
    -- local variables
    location: POINTER;
    pilotFS: PilotFileSystem = LOOPHOLE[fileSystem];
    bufferByteCount: CARDINAL = pilotFS.bufferSize*bytesPerPage;
    block: Stream.Block;
    bytesTransferred: CARDINAL;
    why: Stream.CompletionCode ← normal;
    -- get a scratch space
    spaceH: Space.Handle ← Space.Create[pilotFS.bufferSize, Space.mds];
    Space.Map[spaceH];
    location ← Space.Pointer[spaceH];
    block ←
      [blockPointer: location, startIndex: 0, stopIndexPlusOne: bufferByteCount];
    -- set the byte index to the beginning of the file
    FileStream.SetIndex[pilotFH.streamHandle, 0];
    -- read file
    UNTIL why = endOfStream DO
      [bytesTransferred, why, ] ← Stream.GetBlock[
        pilotFH.streamHandle, block ! FileStream.IndexOutOfRange => EXIT];
      -- this signal can only be generated if the file was empty to start with,
      -- otherwise we would have detected end-of-file and exited.
      -- give the block of data to the caller
      sendBlock[sendBlockData, location, bytesTransferred];
      ENDLOOP;
    -- tell client that there is no more.
    sendBlock[sendBlockData, NIL, 0];
    -- get rid of the scratch space
    Space.Unmap[spaceH];
    Space.Delete[spaceH];
    END;

  WriteFile: ENTRY PROCEDURE [
    fileSystem: FileSystem, fileHandle: FileHandle,
    receiveBlock: PROCEDURE [UNSPECIFIED, POINTER, CARDINAL] RETURNS [CARDINAL],
    receiveBlockData: UNSPECIFIED] =
    BEGIN OPEN pilotFH: LOOPHOLE[fileHandle, PilotFileHandle];
    ENABLE UNWIND => NULL;
    -- Note:  Assumes invocation is consistent with mode declared via OpenFile.
    pilotFS: PilotFileSystem = LOOPHOLE[fileSystem];
    destination: POINTER;
    bufferWordCount: CARDINAL = pilotFS.bufferSize*wordsPerPage;
    length: CARDINAL;
    block: Stream.Block;
    flushFile: BOOLEAN ← FALSE;
    -- get a scratch space
    spaceH: Space.Handle ← Space.Create[pilotFS.bufferSize, Space.mds];
    Space.Map[spaceH];
    destination ← Space.Pointer[spaceH];
    -- set the byte index according to the mode
    FileStream.SetIndex[
      pilotFH.streamHandle,
      IF pilotFH.mode = append THEN FileStream.GetLength[pilotFH.streamHandle]
      ELSE 0];
    -- write file
    UNTIL (length ← receiveBlock[receiveBlockData, destination, bufferWordCount])
      = 0 DO
      block ←
        [blockPointer: destination, startIndex: 0, stopIndexPlusOne: length];
      IF ~flushFile THEN
        Stream.PutBlock[
          pilotFH.streamHandle, block, FALSE !
          Volume.InsufficientSpace => BEGIN flushFile ← TRUE; CONTINUE; END];
      ENDLOOP;
    -- truncate the byte length of the file if the file previously existed and is now smaller.
    -- The file stream package does not truncate the byte length for us.
    FileStream.SetLength[
      pilotFH.streamHandle, FileStream.GetIndex[pilotFH.streamHandle]];
    -- get rid of the scratch space
    Space.Unmap[spaceH];
    Space.Delete[spaceH];
    IF flushFile THEN Abort[noRoomForFile];
    END;

  CloseFile: ENTRY PROCEDURE [
    fileSystem: FileSystem, fileHandle: FileHandle, aborted: BOOLEAN] =
    BEGIN OPEN pilotFH: LOOPHOLE[fileHandle, PilotFileHandle];
    ENABLE UNWIND => NULL;
    -- Note:  On abort, deletes file opened for write, writeThenRead, or readThenWrite.
    -- local variables
    fileName: STRING ← [maxStringLength];
    fileNameL: LONG STRING ← fileName;
    fileNameDesc: LONG DESCRIPTOR FOR ARRAY OF UNSPECIFIED ← DESCRIPTOR[
      fileNameL, SIZE[StringBody [maxStringLength]]];
    Stream.Delete[pilotFH.streamHandle];
    -- close the file stream, may generate a SIGNAL
    -- delete file if appropriate
    IF aborted AND
      (pilotFH.mode = write OR pilotFH.mode = writeThenRead OR pilotFH.mode =
        readThenWrite) THEN
      BEGIN
      -- delete file from directory.
      -- We do not catch any Signals or Errors since we are not doing anything tricky,
      -- and assume that since we opened the file, the capability and name are correct.
      Directory.GetProperty[
        pilotFH.fileCapability, PropertyTypes.tFileName, fileNameDesc];
      Directory.DeleteFile[fileName];
      END;
    -- release pilot file handle object
    Storage.Free[fileHandle];
    END;

  DeleteFile: ENTRY PROCEDURE [fileSystem: FileSystem, file: STRING] =
    BEGIN
    ENABLE
      BEGIN
      UNWIND => NULL;
      Directory.Error =>
        IF type = invalidFileName THEN
          AbortWithExplanation[requestedAccessDenied, file]
        ELSE IF type = directoryNeedsScavenging THEN Abort[requestedAccessDenied];
      File.Error =>
        IF type = immutable OR type = insufficientPermissions THEN
          Abort[requestedAccessDenied];
      END;
    -- local variables
    -- delete file entry from directory
    Directory.DeleteFile[
      file !
      Directory.Error => IF type = fileNotFound THEN Abort[noSuchFile]];
    END;

  RenameFile: ENTRY PROCEDURE [
    fileSystem: FileSystem, currentFile, newFile: STRING] =
    BEGIN
    ENABLE UNWIND => NULL;
    -- local variables
    create: STRING = [maxDateLength];
    author: STRING = [maxDateLength];
    fileInfo: FileInfoObject ← [binary, 8, 0, create, NIL, NIL, author];
    currentFileHandle, newFileHandle: FileHandle ← NIL;
    -- no operation if two filenames equivalent
    IF String.EquivalentString[currentFile, newFile] THEN RETURN;
    -- open current and new files
    [currentFileHandle, ] ← OpenFile[
      fileSystem, currentFile, readThenWrite, FALSE, @fileInfo];
    BEGIN
    ENABLE
      UNWIND =>
        BEGIN
        IF newFileHandle # NIL THEN CloseFile[fileSystem, newFileHandle, TRUE];
        CloseFile[fileSystem, currentFileHandle, FALSE];
        END;
    [newFileHandle, ] ← OpenFile[fileSystem, newFile, write, FALSE, @fileInfo];
    -- transfer contents of current file to new file
    ForkTransferPair[
      fileSystem, ReadFile, currentFileHandle, WriteFile, newFileHandle];
    -- close current and new files
    CloseFile[fileSystem, newFileHandle, FALSE];
    END; -- enable
    -- Note:  aborted=TRUE, requesting deletion of current file.
    CloseFile[fileSystem, currentFileHandle, TRUE];
    END;

  -- **********************!  Subroutines  !***********************

  UniqueFileTag: INTERNAL PROCEDURE RETURNS [LONG INTEGER] =
    BEGIN
    -- generate and return unique file tag; problem if wrap around
    RETURN[uniqueFileTag ← uniqueFileTag + 1];
    END;

  Shorten: PROCEDURE [long: LONG INTEGER] RETURNS [CARDINAL] = INLINE
    BEGIN RETURN[LOOPHOLE[Inline.LowHalf[long], CARDINAL]]; END;

  -- **********************!  Main Program  !***********************

  Directory.CreateSystemDirectory[
    Volume.systemID ! Directory.Error => IF type = fileAlreadyExists THEN CONTINUE];

  END. -- of FTPPilotFile
LOG
Time: September 13, 1979  9:21 AM        By: Dalal        Action: conversion to Pilot 3.0.
Time: September 25, 1979  9:25 AM        By: Dalal        Action: fixed WriteFile bug.
Time: February 10, 1980  12:23 AM        By: Forrest        Action: Changed 0's in xxLeaderPagexx to [0]'s.
Time: August 1, 1980  2:03 PM        By: Marzullo        Action: conversion to new directory interface
Time: August 6, 1980  11:55 AM        By: Evans        Action: Changed EnumerateFiles to non-Entry procedure
Time: August 9, 1980  10:26 PM        By: Sapsford        Action: fix bug in use of Directory.GetNext in Enumerate.  Bruce, Richard, and Keith copied Evans FileInfo fixes earlier today.
Time: August 9, 1980  10:26 PM        By: Bruce        Action: replaced EmptyFileInfoObject usage with code from FTPAltoFile since semantics changed.
Time: August 26, 1980  4:05 PM        By: BLyon        Action: renamed this file