-- PilotSSImpl.mesa  Edited by: Johnsson on  8-Jan-81 18:12:59
-- Edited by: Russ Atkinson on  20-Mar-81 18:07:23
-- Edited by: Paul Rovner on  30-Jul-81  8:51:01 (seg.spare1 on => file is defaultwindow)
-- Edited by: Levin on  8-Dec-81  9:45:40 (bug fixes; monitorize; merge in DummyFileCache)

DIRECTORY
  DCSFileTypes USING [tLeaderPage],
  Directory USING [
    CreateFile, DeleteFile, Error, GetNext, GetProps, ignore, Lookup],
  Environment USING [PageCount, PageNumber, bytesPerPage, wordsPerPage],
  File USING [
    Capability, GetAttributes, GetSize, grow, Permissions, SetSize, ShowCapability, Type],
  FileStream USING [
    Create, GetCapability, GetLeaderProperties, GetLeaderPropertiesForCapability,
    InvalidOperation, NoLeaderPage, SetLeaderProperties, SetLeaderPropertiesForCapability],
  Inline USING [BITAND, BITOR, DIVMOD],
  Segments,
  SegmentsExtra USING[],  -- exports: NewSegmentForSpace
  Space USING [
    Activate, Create, CreateUniformSwapUnits, Deactivate, Delete, ForceOut, GetAttributes,
    GetHandle, Handle, Kill, LongPointer, MakeReadOnly, Map, mds, nullHandle, PageFromLongPointer,
    Unmap, virtualMemory],
  Storage USING [Node, Pages],
  Stream USING [InputOptions, SendNow],
  Streams USING [Address, Handle],
  String USING [AppendString, AppendSubString, SubStringDescriptor],
  Time USING [Current, Packed];
  
PilotSSImpl: MONITOR
  IMPORTS
    Directory, File, FileStream, Inline, Segments, Space, Storage, Stream, String, Time
  EXPORTS SegmentsExtra, Segments, Streams
  SHARES File, Segments =
  BEGIN OPEN Segments;
  
  -- This module has been more-or-less monitorized, but since the interface isn't well-suited
  -- to monitors (e.g., consider the enumeration procedures), I've done it in a rather simple
  -- way.  Simply stated, the monitor is intended to protect separate, independent clients of
  -- this package from screwing each other.  However, two clients who share a segment object
  -- must cooperate externally; this monitor won't protect them.  Only the procedures which
  -- actually manipulate the segTables and fileTables are actually monitored, including the
  -- enumeration guys.  See comments in the enumeration procedures for appropriate caveats.
  -- I claim that the existing functionality has in no way been reduced, only the potential
  -- for evil.  (RL)

  SwapError: PUBLIC SIGNAL [s: SHandle] = CODE;
  InvalidSegment: PUBLIC SIGNAL [s: UNSPECIFIED] = CODE;
  
  DeleteSegment: PUBLIC PROCEDURE [seg: SHandle] =
    BEGIN
    file: FHandle ← seg.file;
    SwapOut[seg];
    IF seg.space # Space.nullHandle THEN Space.Delete[seg.space];
    ReturnSeg[seg];
    IF file # NIL THEN IF (file.lock ← file.lock - 1) = 0 THEN ReleaseFile[file];
    RETURN
    END;
    
  EnumerateSegments: PUBLIC PROCEDURE [
    proc: PROCEDURE [SHandle] RETURNS [BOOLEAN]] RETURNS [f: SHandle] =
    BEGIN
    -- Note:  once we have a pointer to a page of segment objects, the tail of
    -- the chain is guaranteed to be good.  This is because no pages of the
    -- objects are ever freed, and new pages are only added at the front.  So,
    -- we needn't stand on our heads to unlock the monitor around the call to
    -- 'proc'; we just unlock it as soon as we have stashed the head.  Of course,
    -- we can't guarantee that the caller of the enumerator will see a consistent
    -- snapshot of the segment table, but that guarantee was never present in the
    -- interface anyway, so no functionality has been lost.
    Init: ENTRY PROCEDURE RETURNS [STableHandle] = INLINE {RETURN[segTables]};
    FOR t: STableHandle ← Init[], t.link UNTIL t = NIL DO
      FOR i: CARDINAL IN [0..SegsPerTable) DO
	f ← @t.segs[i];
	IF f.inuse AND proc[f] THEN RETURN[f];
	ENDLOOP;
      ENDLOOP;
    RETURN[NIL]
    END;
    
  FlushSegmentCache: PUBLIC PROCEDURE = {};
  
  Kill: PUBLIC PROCEDURE [seg: SHandle, base: PageNumber ← DefaultBase] =
    BEGIN
    IF seg.mapped THEN Space.Kill[seg.space] ELSE seg.killed ← TRUE;
    RETURN
    END;
    
  MakeReadOnly: PUBLIC PROCEDURE [seg: SHandle] =
    BEGIN
    ValidateSeg[seg];
    IF seg.mapped THEN Space.MakeReadOnly[seg.space];
    seg.write ← FALSE;
    RETURN
    END;
    
  MoveSegment: PUBLIC PROCEDURE [
    seg: SHandle, base: Environment.PageNumber, pages: Environment.PageCount] =
    BEGIN
    IF IsVMSeg[seg] THEN ERROR SwapError[seg];
    SwapOut[seg];
    IF seg.space # Space.nullHandle THEN {
      IF seg.pages < pages THEN {
        Space.Delete[seg.space]; seg.space ← Space.nullHandle; seg.mapped ← FALSE}
      ELSE IF seg.mapped THEN {Space.Unmap[seg.space]; seg.mapped ← FALSE}};
    seg.base ← IF base = DefaultBase THEN 1 ELSE base;
    seg.pages ← pages;
    IF seg.base # 1 AND File.GetSize[seg.file.cap] < seg.base + pages THEN SIGNAL SwapError[seg];
    RETURN
    END;
    
  NewSegment: PUBLIC PROCEDURE [
    file: FHandle, base: Environment.PageNumber, pages: Environment.PageCount,
    access: Access ← DefaultAccess]
    RETURNS [s: SHandle] =
    BEGIN
    LockFile[file];
    s ← NewSegmentCommon[access];
    s.file ← file;
    s.base ← IF base = DefaultBase THEN 1 ELSE base;
    s.pages ← pages;
    END;
    
  NewSegmentForSpace: PUBLIC PROCEDURE [space: Space.Handle, access: Access ← DefaultAccess]
    RETURNS [s: SHandle] =
    BEGIN
    s ← NewSegmentCommon[access];
    s.space ← space;
    s.base ← 1;
    s.pages ← Space.GetAttributes[space].size;
    s.mapped ← s.spare1 ← TRUE;
    END;
    
  SegmentAddress: PUBLIC PROCEDURE [seg: SHandle] RETURNS [Address] =
    BEGIN
    ValidateSeg[seg];
    IF ~seg.mapped THEN ERROR SwapError[seg];
    RETURN[Space.LongPointer[seg.space]];
    END;
    
  SwapIn: PUBLIC PROCEDURE [
    seg: SHandle, base: PageNumber ← DefaultANYBase, info: AllocInfo ← EasyUp] =
    BEGIN OPEN Space;
    ValidateSeg[seg];
    IF seg.lock = MaxSegLocks THEN ERROR SwapError[seg];
    IF ~seg.mapped THEN
      IF IsVMSeg[seg] THEN ERROR SwapError[seg]
      ELSE
      BEGIN
      cap: File.Capability ← seg.file.cap;
      type: File.Type ← File.GetAttributes[cap].type;
      pageOffset: CARDINAL ← 1;
      IF type = DCSFileTypes.tLeaderPage THEN pageOffset ← 0;
      IF seg.space = Space.nullHandle THEN {
        seg.space ← Space.Create[
	  size: seg.pages,
	  parent: IF base = DefaultMDSBase THEN mds ELSE virtualMemory];
        IF seg.pages > 7 THEN
	  Space.CreateUniformSwapUnits[parent: seg.space, size: 4]};
      cap.permissions ← IF seg.write THEN Read+Write ELSE Read;
      Space.Map[space: seg.space,
	window: [file: cap, base: seg.base-pageOffset]];
      IF seg.killed THEN Space.Kill[seg.space];
      Space.Activate[seg.space];
      seg.mapped ← TRUE;
      seg.killed ← FALSE;
      IF seg.write THEN {
	c: Time.Packed = Time.Current[];
	SetFileTimes[file: seg.file, create: c, read: c, write: c]}
      ELSE SetFileTimes[file: seg.file, read: Time.Current[]];
      END;
    seg.lock ← seg.lock+1;
    RETURN
    END;
    
  SwapOut: PUBLIC PROCEDURE [seg: SHandle] =
    BEGIN
    ValidateSeg[seg];
    IF ~seg.mapped THEN RETURN;
    IF seg.lock > 0 THEN ERROR SwapError[seg];
    Space.Deactivate[seg.space];
    RETURN
    END;
    
  SwapUp: PUBLIC PROCEDURE [seg: SHandle] =
    BEGIN
    ValidateSeg[seg];
    IF seg.mapped THEN Space.ForceOut[seg.space];
    RETURN
    END;
    
  Unlock: PUBLIC PROCEDURE [seg: SHandle] =
    BEGIN
    ValidateSeg[seg];
    IF seg.lock=0 THEN ERROR SwapError[seg];
    seg.lock ← seg.lock-1;
    RETURN
    END;
    
  VMtoSegment: PUBLIC PROCEDURE [a: Address] RETURNS [SHandle] =
    BEGIN
    space, parent: Space.Handle;
    mapped: BOOLEAN;
    FindSeg: PROCEDURE [seg: SHandle] RETURNS [BOOLEAN] =
      BEGIN RETURN[seg.space = space] END;
    space ← Space.GetHandle[Space.PageFromLongPointer[a]];
    DO
      IF space = Space.mds OR space = Space.virtualMemory THEN RETURN[NIL];
      [parent: parent, mapped: mapped] ← Space.GetAttributes[space];
      IF mapped THEN EXIT;
      space ← parent;
      ENDLOOP;
    RETURN[EnumerateSegments[FindSeg]];
    END;
    
    
  -- File Routines
  
  FileError: PUBLIC SIGNAL [f: FHandle] = CODE;
  InvalidFile: PUBLIC SIGNAL [f: UNSPECIFIED] = CODE;
  
  DestroyFile: PUBLIC PROCEDURE [file: FHandle] = 
    BEGIN
    name: STRING ← [100];
    NameForFile[name, file];
    Directory.DeleteFile[name];
    END;

  ModifyFile: PUBLIC PROCEDURE [name: STRING] RETURNS [BOOLEAN] = 
    BEGIN
    cap: File.Capability;
    okay: BOOLEAN ← TRUE;
    -- Note:  once we have a pointer to a StatItem, the tail of
    -- the chain is guaranteed to be good.  This is because no StatItems
    -- are ever freed, and new StatItems are only added at the front.  So,
    -- we needn't stand on our heads to unlock the monitor around the call to
    -- 'proc'; we just unlock it as soon as we have stashed the head.  Of course,
    -- we can't guarantee that ModifyFile will see a consistent
    -- snapshot of the StatItem list, but that guarantee was never present in the
    -- interface anyway, so no functionality has been lost.
    Init: ENTRY PROCEDURE RETURNS [POINTER TO StatItem] = INLINE {RETURN[statHead]};
    CheckFHandle: PROCEDURE [file: FHandle] RETURNS [BOOLEAN] =
      BEGIN
      IF file.lock # 0 AND
	File.ShowCapability[cap].fID = File.ShowCapability[file.cap].fID THEN
	  BEGIN
	  FOR p: POINTER TO StatItem ← Init[], p.link UNTIL p = NIL DO
	    okay ← okay AND p.proc[name, file]
	    ENDLOOP;
	  okay ← okay AND (~file.inuse OR file.lock = 0);
	  RETURN[okay];
	  END;
      RETURN[FALSE];
      END;
    FOR p: POINTER TO StatItem ← Init[], p.link UNTIL p = NIL DO
      IF ~(okay ← okay AND p.proc[name, NIL]) THEN EXIT;
      ENDLOOP;
    IF okay THEN {
      cap ← Directory.Lookup[fileName: name, permissions: Directory.ignore
	! Directory.Error => GOTO error];
      [] ← EnumerateFiles[CheckFHandle]};
    RETURN[okay];
    EXITS error => RETURN[TRUE];
    END;

  StatItem: TYPE = RECORD [
    link: POINTER TO StatItem, proc: PROC[STRING,FHandle] RETURNS [BOOLEAN]];

  statHead: POINTER TO StatItem ← NIL;

  AddModifyProc: PUBLIC ENTRY PROC [proc: PROC[STRING,FHandle] RETURNS [BOOLEAN]] = {
    p: POINTER TO StatItem = Storage.Node[SIZE[StatItem]];
    p↑ ← [link: statHead, proc: proc];
    statHead ← p};

  NewFile: PUBLIC PROCEDURE [
    name: STRING,
    access: Access ← DefaultAccess,
    version: VersionOptions ← DefaultVersion] RETURNS [file: FHandle] =
    BEGIN
    type: File.Type ← DCSFileTypes.tLeaderPage;
    old, create: BOOLEAN;
    cap: File.Capability;
    dot: CARDINAL = name.length-1;
    IF name[dot] = '. THEN name.length ← dot;
    [access,version] ← ValidateOptions[access,version];
    create ← version # OldFileOnly;
    IF create THEN
      BEGIN
      bogus: BOOLEAN ← FALSE;
      old ← FALSE;
      cap ← Directory.CreateFile[name,type,0 ! Directory.Error => {
	IF type = fileAlreadyExists THEN old ← TRUE ELSE bogus ← TRUE; CONTINUE}];
      IF bogus OR (old AND version = NewFileOnly) THEN ERROR FileNameError[name];
      IF old THEN cap ← Directory.Lookup[
	fileName: name, permissions: Directory.ignore ! Directory.Error =>
	  ERROR FileNameError[name]];
      END
    ELSE cap ← Directory.Lookup[
      fileName: name, permissions: Directory.ignore ! Directory.Error =>
	ERROR FileNameError[name]];
    file ← InsertFile[@cap, access];
    END;

  FileNameError: PUBLIC SIGNAL [name: STRING] = CODE;

  ValidateOptions: PROCEDURE [
    access: Access, version: VersionOptions]
    RETURNS [Access, VersionOptions] =
    BEGIN OPEN Inline;
    IF access = DefaultAccess THEN access ← Read;
    -- IF version = DefaultVersion THEN version ← 0;
    IF BITAND[version, NewFileOnly+OldFileOnly] = NewFileOnly+OldFileOnly
    OR (BITAND[version, NewFileOnly]#0 AND BITAND[access, File.grow]=0)
      THEN ERROR FileError[NIL];
    IF BITAND[access,File.grow]=0 THEN
      version ← BITOR[version,OldFileOnly];
    RETURN[access, version]
    END;

  NameForFile: PUBLIC PROCEDURE [name: STRING, file: FHandle] =
    BEGIN
    name.length ← 0;
    [] ← Directory.GetProps[file.cap, name ! Directory.Error => {
      String.AppendString[name, "???"L]; CONTINUE}];
    RETURN
    END;

  EnumerateDirectory: PUBLIC PROC [
      proc: PROC [POINTER TO FP, STRING] RETURNS [BOOLEAN],
      files: STRING ← NIL,
      wantWholeName: BOOLEAN ← FALSE] =
    BEGIN
    next: STRING ← [100];
    name: STRING ← [100];
    cap: File.Capability;
    IF files = NIL THEN files ← "*"L;
    DO
      cap ← Directory.GetNext[pathName: files, currentName: next, nextName: next ! Directory.Error => CONTINUE];
      IF next.length = 0 THEN EXIT;
      StripQualification[from: next, to: name, all: wantWholeName];
      IF proc[@cap, name] THEN EXIT;
      ENDLOOP;
    END;

  StripQualification: PROC [from, to: STRING, all: BOOLEAN] = 
    BEGIN
    split: String.SubStringDescriptor ← [base: from, length: , offset: ];
    IF from.length = 0 THEN RETURN;
    IF all THEN {String.AppendString[to, from]; RETURN};
    FOR i: CARDINAL DECREASING IN [0.. from.length) DO
      IF from[i] = '> THEN {split.offset ← i+1;  EXIT}; 
      ENDLOOP;
    split.length ← from.length-split.offset;
    to.length ← 0;
    String.AppendSubString[to, @split];
    StripDot[to];
    END;

  StripDot: PROCEDURE [s: STRING] = INLINE
    BEGIN
    dot: CARDINAL;
    IF s = NIL OR s.length = 0 THEN RETURN;
    IF s[dot ← (s.length - 1)] = '. THEN s.length ← dot;
    END;

  InvalidateFileCache, FlushFileCache: PUBLIC PROC = {};

  EnumerateFiles: PUBLIC --ENTRY-- PROCEDURE [
    proc: PROCEDURE [FHandle] RETURNS [BOOLEAN]] RETURNS [f: FHandle] =
    BEGIN
    -- Note:  once we have a pointer to a page of file objects, the tail of
    -- the chain is guaranteed to be good.  This is because no pages of the
    -- objects are ever freed, and new pages are only added at the front.  So,
    -- we needn't stand on our heads to unlock the monitor around the call to
    -- 'proc'; we just unlock it as soon as we have stashed the head.  Of course,
    -- we can't guarantee that the caller of the enumerator will see a consistent
    -- snapshot of the file table, but that guarantee was never present in the
    -- interface anyway, so no functionality has been lost.
    Init: ENTRY PROCEDURE RETURNS [FTableHandle] = INLINE {RETURN[fileTables]};
    FOR t: FTableHandle ← fileTables, t.link UNTIL t = NIL DO
      FOR i: CARDINAL IN [0..FilesPerTable) DO
	f ← @t.files[i];
	IF f.inuse AND proc[f] THEN RETURN[f];
	ENDLOOP;
      ENDLOOP;
    RETURN[NIL]
    END;
    
  GetFileProperties: PUBLIC PROCEDURE [file: FHandle]
    RETURNS [create, write, read: Time.Packed, length: LONG CARDINAL] =
    BEGIN
    [create: create, write: write, read: read, length: length] ←
      FileStream.GetLeaderPropertiesForCapability[file.cap
	!FileStream.NoLeaderPage => {
	  create←write←read←[0];
	  length ← File.GetSize[file.cap] * 512;
	  CONTINUE}]
    END;
    
  GetFileTimes: PUBLIC PROCEDURE [file: FHandle]
    RETURNS [create, write, read: Time.Packed] =
    BEGIN
    [create: create, write: write, read: read] ←
      FileStream.GetLeaderPropertiesForCapability[file.cap
	!FileStream.NoLeaderPage => {create←write←read←[0]; CONTINUE}]
    END;
    
  GetFileLength: PUBLIC PROCEDURE [file: FHandle]
    RETURNS [length: LONG CARDINAL] =
    BEGIN
    length ← FileStream.GetLeaderPropertiesForCapability[file.cap
	!FileStream.NoLeaderPage => {
	  length ← File.GetSize[file.cap] * 512;
	  CONTINUE}].length
    END;
    
  InsertFile: PUBLIC ENTRY PROCEDURE [
    file: FPHandle, access: Access ← DefaultAccess] RETURNS [f: FHandle] =
    BEGIN
    -- Things are a bit tricky here, since it really is important that
    -- only a single FHandle exist per file ID.  Thus, the enumeration
    -- and potential subsequent GetFile must be done with the monitor
    -- locked.  Unfortunately, this means we can't use the standard
    -- EnumerateFiles procedure, so we roll our own local version.
    FOR t: FTableHandle ← fileTables, t.link UNTIL t = NIL DO
      FOR i: CARDINAL IN [0..FilesPerTable) DO
	f ← @t.files[i];
	IF f.inuse AND f.cap.fID = file.fID THEN RETURN;
	ENDLOOP;
      REPEAT
        FINISHED =>
	  BEGIN
          f ← GetFile[];
          f↑ ← [cap: file↑, inuse: TRUE, lock: 0, link: NIL, spare1: FALSE,
            spare2: FALSE, spare3: FALSE];
	  END;
      ENDLOOP;
    END;
    
  LockFile: PUBLIC PROCEDURE [file: FHandle] =
    BEGIN
    IF file.lock = MaxFileLocks THEN ERROR FileError[file];
    file.lock ← file.lock + 1;
    RETURN
    END;
    
  ReleaseFile: PUBLIC PROCEDURE [file: FHandle] =
    BEGIN
    IF file.lock # 0 THEN RETURN;
    ReturnFile[file];
    RETURN
    END;
    
  SetFileLength: PUBLIC PROCEDURE [file: FHandle, length: LONG CARDINAL] =
    BEGIN
    cap: File.Capability ← file.cap;
    cap.permissions ← AllAccess;
    File.SetSize[
      file: cap,
      size: (length+Environment.bytesPerPage-1)/Environment.bytesPerPage]
    END;
    
  SetFileTimes: PUBLIC PROCEDURE [file: FHandle, create, write, read: Time.Packed ← [0]] =
    BEGIN
    FileStream.SetLeaderPropertiesForCapability[
      cap: file.cap, create: create, write: write, read: read
	!FileStream.NoLeaderPage => CONTINUE]
    END;
    
  UnlockFile: PUBLIC PROCEDURE [file: FHandle] =
    BEGIN
    IF file.lock = 0 THEN ERROR FileError[file];
    file.lock ← file.lock - 1;
    RETURN
    END;
    
    
  -- Seg Sub-Routines
  
  freeSegs: SHandle ← NIL;
  segTables: STableHandle ← NIL;
  
  SegsPerTable: CARDINAL = (Environment.wordsPerPage-1)/SIZE[SObject];
  
  STable: TYPE = RECORD [
    link: STableHandle,
    segs: ARRAY [0..SegsPerTable) OF SObject];
    
  STableHandle: TYPE = POINTER TO STable;
  
  NewSegmentCommon: PROCEDURE [access: Access] RETURNS [s: SHandle] =
    BEGIN
    s ← GetSeg[];
    s.file ← NIL;
    s.space ← Space.nullHandle;
    s.inuse ← TRUE;
    s.mapped ← s.killed ← s.spare1 ← FALSE;
    s.write ← IF access = DefaultAccess OR access = Read THEN FALSE ELSE TRUE;
    s.lock ← 0;
    END;
    
  ValidateSeg: PUBLIC ENTRY PROCEDURE [s: SHandle] =
    BEGIN OPEN Inline;
    table: STableHandle ← BITAND[s, 177400B];
    t: STableHandle;
    i,j: CARDINAL;
    FOR t ← segTables, t.link UNTIL t = NIL DO
      IF t = table THEN EXIT;
      REPEAT FINISHED => ERROR InvalidSegment[s];
      ENDLOOP;
    [i, j] ← DIVMOD[s-@table.segs[0],SIZE[SObject]];
    IF j#0 OR ~s.inuse THEN ERROR InvalidSegment[s];
    RETURN
    END;
    
  GetNewSegTable: INTERNAL PROCEDURE = INLINE
    BEGIN
    t: STableHandle ← Storage.Pages[1];
    i: CARDINAL;
    FOR i IN [0..SegsPerTable) DO ReturnSegInternal[@t.segs[i]]; ENDLOOP;
    t.link ← segTables;
    segTables ← t;
    RETURN
    END;
    
  GetSeg: ENTRY PROCEDURE RETURNS [f: SHandle] = INLINE
    BEGIN
    IF freeSegs = NIL THEN GetNewSegTable[];
    f ← freeSegs;
    freeSegs ← f.link;
    RETURN
    END;
    
  ReturnSeg: ENTRY PROCEDURE [f: SHandle] = INLINE {ReturnSegInternal[f]};

  ReturnSegInternal: INTERNAL PROCEDURE [f: SHandle] =
    BEGIN
    f.inuse ← FALSE;  
    f.link ← freeSegs;  freeSegs ← f;
    RETURN
    END;
    
  IsVMSeg: PROCEDURE [seg: SHandle] RETURNS [BOOLEAN] = INLINE {RETURN[seg.spare1]};
    
  -- File Sub-Routines
  
  freeFiles: FHandle ← NIL;
  fileTables: FTableHandle ← NIL;
  
  FilesPerTable: CARDINAL = (Environment.wordsPerPage-1)/SIZE[FObject];
  
  FTable: TYPE = RECORD [
    link: FTableHandle,
    files: ARRAY [0..FilesPerTable) OF FObject];
    
  FTableHandle: TYPE = POINTER TO FTable;
  
  ValidateFile: PUBLIC ENTRY PROCEDURE [f: FHandle] =
    BEGIN OPEN Inline;
    table: FTableHandle ← BITAND[f, 177400B];
    t: FTableHandle;
    i,j: CARDINAL;
    FOR t ← fileTables, t.link UNTIL t = NIL DO
      IF t = table THEN EXIT;
      REPEAT FINISHED => ERROR InvalidFile[f];
      ENDLOOP;
    [i, j] ← DIVMOD[f-@table.files[0],SIZE[FObject]];
    IF j#0 OR ~f.inuse THEN ERROR InvalidFile[f];
    RETURN
    END;
    
  GetFile: INTERNAL PROCEDURE RETURNS [f: FHandle] =
    BEGIN
    IF freeFiles = NIL THEN GetNewFileTable[];
    f ← freeFiles;
    freeFiles ← f.link;
    f.inuse ← TRUE;
    RETURN
    END;
    
  ReturnFile: ENTRY PROCEDURE [f: FHandle] = INLINE {ReturnFileInternal[f]};

  GetNewFileTable: INTERNAL PROCEDURE = INLINE
    BEGIN
    t: FTableHandle ← Storage.Pages[1];
    i: CARDINAL;
    FOR i IN [0..FilesPerTable) DO ReturnFileInternal[@t.files[i]]; ENDLOOP;
    t.link ← fileTables;
    fileTables ← t;
    RETURN
    END;
    
  ReturnFileInternal: INTERNAL PROCEDURE [f: FHandle] =
    BEGIN
    f.inuse ← FALSE;  
    f.link ← freeFiles;  freeFiles ← f;
    RETURN
    END;
    
  -- Streams implementation
  
  Cleanup: PUBLIC PROCEDURE [h: Streams.Handle] =
    BEGIN
    Stream.SendNow[h ! FileStream.InvalidOperation => CONTINUE];
    END;
    
  CreateStream: PUBLIC PROCEDURE [file: FHandle, access: Access ← Read]
    RETURNS [Streams.Handle] =
    BEGIN
    op: Stream.InputOptions = [
      signalEndOfStream: TRUE,
      signalShortBlock: FALSE,
      signalLongBlock: FALSE,
      signalSSTChange: FALSE,
      terminateOnEndPhysicalRecord: FALSE];
    LockFile[file];
    RETURN[FileStream.Create[[file.cap.fID, access], op]]
    END;
    
  Destroy: PUBLIC PROCEDURE [h: Streams.Handle] = {
    file: FHandle = FileFromStream[h];
    UnlockFile[file];
    IF ReleasableFile[file] THEN ReleaseFile[file];
    h.delete[h]};
    
  FileFromStream: PUBLIC PROCEDURE [
    h: Streams.Handle] RETURNS [file: FHandle] = {
    cap: File.Capability ← FileStream.GetCapability[h];
    file ← InsertFile[@cap, AllAccess];
    IF ReleasableFile[file] THEN LockFile[file]};
    
  GetTimes: PUBLIC PROCEDURE [h: Streams.Handle]
    RETURNS [create, write, read: Time.Packed] =
    BEGIN
    [create: create, write: write, read: read] ←
      FileStream.GetLeaderProperties[h]
    END;
    
  NewStream: PUBLIC PROCEDURE [name: STRING, access: Access ← Read]
    RETURNS [Streams.Handle] =
    BEGIN
    RETURN[CreateStream[NewFile[name, access], access]]
    END;
    
  SetTimes: PUBLIC PROCEDURE [
    h: Streams.Handle, create, write, read: Time.Packed] =
    BEGIN
    FileStream.SetLeaderProperties[
      sH: h, create: create, write: write, read: read]
    END;
    
  GetBlock: PUBLIC PROCEDURE [
    h: Streams.Handle, a: Streams.Address, words: CARDINAL]
    RETURNS [CARDINAL] =
    BEGIN
    NoOptions: Stream.InputOptions = [FALSE, FALSE, FALSE, FALSE, FALSE];
    RETURN[(h.get[h,
      [blockPointer: a, startIndex: 0, stopIndexPlusOne: words*2],
      NoOptions].bytesTransferred+1)/2];
    END;
    
  PutBlock: PUBLIC PROCEDURE [
    h: Streams.Handle, a: Streams.Address, words: CARDINAL]
    RETURNS [CARDINAL] =
    BEGIN
    h.put[h,
      [blockPointer: a, startIndex: 0, stopIndexPlusOne: words*2],
      FALSE];
    RETURN[words]
    END;
    
    
    
END.