-- CheckIncludes.Mesa  
-- Last modified by Sandman on July 8, 1980  9:19 AM
-- Last modified by Lewis on October 14, 1980  11:09 AM
-- Copyright  Xerox Corporation 1979, 1980

DIRECTORY
  AltoDefs USING [PageCount, PageNumber],
  AltoFileDefs USING [CFA, FilenameChars, FP],
  BcdDefs USING [
    BCD, FTNull, FTSelf, MTIndex, SGIndex, VersionID, VersionStamp, Base],
  BcdOps USING [FTHandle, NameString, SGHandle],
  DirectoryDefs USING [EnumerateDirectory],
  FileLists USING [
    feb, ifb, ifdb, EnlargingTables, DoneEnlargingTables, fileList, FE, FEnil,
    IncFile, InclusionDepth, IFnil, NullStamp, NullTime, IncFileDesc, IFDnil,
    Initialize, Finalize, InsertInUserList, IsInUserList, InsertInFileList,
    InsertIncludeFileItem],
  ImageDefs USING [BcdTime, StopMesa],
  IncludesSymTables USING [
    mdb, mdLimit, ssb, ht, LoadSymTables, ReleaseSymTables,
    ObsoleteSymbolTable, UnlockSymFileSegments, ReloadSymFileSegments],
  IODefs USING [
    CR, SP, FF, NumberFormat, ReadID, Rubout, WriteChar, WriteLine,
    WriteString],
  MiscDefs USING [CommandLineCFA],
  OutputDefs USING [
    CloseOutput, OpenOutput, PutChar, PutCR, PutNumber, PutString, PutTime],
  SegmentDefs USING [
    DefaultAccess, DefaultVersion, DeleteFileSegment, FileHandle,
    FileSegmentAddress, FileSegmentHandle, InsertFile, LockFile,
    MoveFileSegment, NewFile, NewFileSegment, Read, SwapIn, Unlock,
    UnlockFile],
  SourceTime USING [FindSourceVersion],
  StreamDefs USING [
    CreateByteStream, GetIndex, JumpToFA, ModifyIndex, Read, SetIndex,
    StreamError, StreamHandle],
  String USING [
    AppendChar, AppendString, AppendSubString, EquivalentString, SubString,
    SubStringDescriptor],
  Symbols USING [HTIndex, HTNull, MDIndex, MDRecord, NullFileIndex],
  TimeDefs USING [AppendDayTime, DefaultTime, PackedTime, UnpackDT];

CheckIncludes: PROGRAM
  IMPORTS
    DirectoryDefs, FileLists, IODefs, ImageDefs, IncludesSymTables, MiscDefs,
    OutputDefs, SegmentDefs, SourceTime, String, TimeDefs, StreamDefs =
  BEGIN OPEN SegmentDefs, FileLists;
  
 -- USER-SPECIFIED SWITCHES
  
  SwitchTypes: TYPE = -- default is /io~c~m~n~p~t~d 
    {consistent, includes, multiple, order, pause, dateFromText,
    noCompIfNotOnDisk, debug};
  Switches: PACKED ARRAY SwitchTypes OF BOOLEAN ←
    [FALSE, TRUE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE];

  
 -- INITIALIZATION AND FINALIZATION
  
  commandStream: StreamDefs.StreamHandle;
  outputFileName: STRING ← [AltoFileDefs.FilenameChars + 1];
  
  Initialize: PROC =
    BEGIN
    PutHeading[];
    GetOutputFileAndSwitches[];
    FileLists.Initialize[Switches[debug]];
    GetInputFileNames[];
    END;
    
  Finalize: PROC =
    {FileLists.Finalize[Switches[debug]]};
    
  PutHeading: PROC =
    BEGIN OPEN TimeDefs, IODefs;
    herald: STRING ← [60];
    WriteChar[CR];
    String.AppendString[herald, "Alto/Mesa IncludeChecker 6.0 of "L];
    AppendDayTime[herald, UnpackDT[ImageDefs.BcdTime[]]];
    herald.length ← herald.length - 3;
    WriteLine[herald];
    herald.length ← 0;
    String.AppendString[herald, "  "L];
    AppendDayTime[herald, UnpackDT[DefaultTime]];
    herald.length ← herald.length - 3;
    WriteLine[herald];
    END;
    
  GetOutputFileAndSwitches: PROC =
    BEGIN OPEN IODefs, StreamDefs;
    cfa: POINTER TO AltoFileDefs.CFA ← MiscDefs.CommandLineCFA[];
    commandStream ← CreateByteStream[
      SegmentDefs.InsertFile[@cfa.fp, Read], Read];
    JumpToFA[commandStream, @cfa.fa];
    BEGIN
    WHILE commandStream.get[commandStream ! StreamError => GOTO noFileNames] <=
      IODefs.SP DO NULL ENDLOOP;
    SetIndex[commandStream, ModifyIndex[GetIndex[commandStream], -1]];
    EXITS
      noFileNames =>
	{commandStream.destroy[commandStream]; commandStream ← NIL};
    END;
    WriteChar[CR];
    GetToken["Output file name/switches? "L, outputFileName];
    SetSwitches[outputFileName];
    IF outputFileName.length = 0 THEN
      String.AppendString[outputFileName, "Includes"L];
    END;
    
  GetInputFileNames: PROC =
    BEGIN OPEN IODefs;
    fileName: STRING ← [AltoFileDefs.FilenameChars + 1];
    IF commandStream = NIL THEN WriteLine["Input file names?"L];
    GetToken["  File: "L, fileName];
    UNTIL fileName.length = 0 DO 
      FileLists.InsertInUserList[fileName];
      GetToken["  File: "L, fileName];
      ENDLOOP;
    IF commandStream = NIL THEN WriteChar[CR];
    END;
    
  GetToken: PROC [prompt, name: STRING] =
    BEGIN OPEN IODefs;
    c: CHARACTER;
    IF commandStream = NIL THEN
      BEGIN
      WriteString[prompt];
      ReadID[name 
        ! Rubout => {WriteLine[" XXX"]; WriteString[prompt]; RETRY}];
      WriteChar[CR];
      WHILE String.EquivalentString[name, "?"L] DO
	DisplayUsageInfo[];
	WriteString[prompt];
	ReadID[name 
          ! Rubout => {WriteLine[" XXX"]; WriteString[prompt]; RETRY}];
	WriteChar[CR];
	ENDLOOP;
      END
    ELSE
      BEGIN
      name.length ← 0;
      UNTIL commandStream.endof[commandStream] DO
	c ← commandStream.get[commandStream];
	SELECT c FROM
	  SP, CR => IF name.length > 0 THEN RETURN;
	  ENDCASE => String.AppendChar[name, c];
	ENDLOOP;
      END;
    END;
    
  DisplayUsageInfo: PROC =
    BEGIN OPEN IODefs;
    WriteLine[
      "  If an empty output file name is given, the file ""Includes.list"" is assumed."L];
    WriteLine[
      "  If no extension is given for the output file, "".list"" is assumed."L];
    WriteLine[
      "  Switches may follow the output file name after a ""/"".  A ""~"" turns them off."L];
    WriteLine["  The switches are:"L];
    WriteLine[
      "    C (consistent compilation command), I (includes/included by relations),"L];
    WriteLine["    M (multiple output files), N (compile only files with Bcds on disk),"L];
    WriteLine["    O (compilation order),"L];
    WriteLine[
      "    P (put ""/p"" after last definitions file in compilation command,"L];
    WriteLine["    S (same as C-I-O), T (source file creation date from text)."L];
    WriteLine["  The default switches are IO~C~M~N~T~P."L];
    WriteLine["  An empty file name terminates the list of input files."L];
    WriteLine[
      "  If no names are given, all source and bcd files on the disk are processed."L];
    WriteChar[CR];
    END;
    
  SetSwitches: PROC [s: STRING] =
    BEGIN
    i, start: CARDINAL;
    notMinus: BOOLEAN ← TRUE;
    FOR i IN [0..s.length) DO
      IF s[i] = '/ THEN {start ← i; EXIT};
      REPEAT 
	FINISHED => RETURN;
      ENDLOOP;
    FOR i IN (start..s.length) DO
      SELECT s[
	i] FROM
	'/ => LOOP;
	'-, '~ => {notMinus ← FALSE; LOOP};
	'c, 'C => Switches[consistent] ← notMinus;
	'i, 'I => Switches[includes] ← notMinus;
	'm, 'M => Switches[multiple] ← notMinus;
	'n, 'N => Switches[noCompIfNotOnDisk] ← notMinus;
	'o, 'O => Switches[order] ← notMinus;
	's, 'S =>
	  IF notMinus THEN -- star hack (=C~I~O)
	    BEGIN
	    Switches[consistent] ← TRUE;
	    Switches[includes] ← Switches[order] ← FALSE;
	    END;
	'p, 'P => Switches[pause] ← notMinus;
	't, 'T => Switches[dateFromText] ← notMinus;
	'd, 'D => Switches[debug] ← notMinus;
	ENDCASE => LOOP;
      notMinus ← TRUE;
      ENDLOOP;
    s.length ← start;
    END;
    
    
 -- ADD USER-SPECIFIED FILES TO FILELIST, AND ANY FILES THEY DIRECTLY INCLUDE
  
  AddUserSpecifiedFiles: PROC =
    BEGIN OPEN IODefs;
    
    CheckOneFile: PROC [
        fp: POINTER TO AltoFileDefs.FP, dirName: STRING]
        RETURNS [stop: BOOLEAN] =
      BEGIN
      fileName: STRING ← [AltoFileDefs.FilenameChars + 1];
      ext: STRING ← [AltoFileDefs.FilenameChars + 1];
      mesa, bcd: BOOLEAN ← FALSE;
      file: SegmentDefs.FileHandle;
      SplitFileName[wholename: dirName, name: fileName, ext: ext];
      IF String.EquivalentString[ext, "mesa"] THEN mesa ← TRUE
      ELSE
        IF String.EquivalentString[ext, "bcd"] THEN bcd ← TRUE 
	ELSE RETURN[FALSE];
      IF FileLists.IsInUserList[fileName] THEN
        BEGIN
        file ← InsertFile[fp, Read];
        LockFile[file];
        IF mesa THEN AddSourceFile[file, fileName]
        ELSE AddObjectFile[file, fileName];
        UnlockFile[file];
        END;
      RETURN[FALSE]
      END;

    WriteLine["Processing file:"L];
    DirectoryDefs.EnumerateDirectory[CheckOneFile];
    END;
    
  SplitFileName: PROC [wholename, name, ext: STRING] =
    BEGIN
    i: CARDINAL;
    active: STRING ← name;
    name.length ← ext.length ← 0;
    FOR i IN [0..wholename.length) DO
      IF wholename[i] = '. THEN active ← ext
      ELSE String.AppendChar[active, wholename[i]];
      ENDLOOP;
    END;

    
  AddSourceFile: PROC [sourceFile: FileHandle, fileName: STRING] =
    BEGIN OPEN IODefs;
    fe: FileLists.FE;
    WriteString["  "L];  WriteString[fileName];  WriteLine[".mesa"L];
    fe ← FileLists.InsertInFileList[fileName];
    feb[fe].source ← TRUE;
    feb[fe].sourceTime ← SourceTime.FindSourceVersion[
      sourceFile, Switches[dateFromText]];
    END;

    
  NotCompilerBcd: ERROR = CODE; -- Binder created or no symbol segment
  ObsoleteBcd: ERROR = CODE; -- Bcd or symbol table version not current
  CompilerSmashedBcd: ERROR = CODE; -- File had compilation errors
  ErroneousBcd: ERROR = CODE;
  
  AddObjectFile: PROC [bcdFile: FileHandle, fileName: STRING] =
    BEGIN OPEN String, IODefs;
    symFile: FileHandle;
    symSegBase, symSegSize: AltoDefs.PageNumber;
    bcdVersion: BcdDefs.VersionStamp;
    bcdSourceTime: LONG CARDINAL;
    defModule, notAlto, crossJumped, longAlto, tableCompiled: BOOLEAN;
    fe: FileLists.FE;
    BEGIN
    [bcdVersion, bcdSourceTime, symFile, symSegBase, symSegSize, defModule,
      notAlto, crossJumped, longAlto, tableCompiled] ← ExamineBcd[bcdFile 
	! NotCompilerBcd => GOTO ignoreBcd;
          ObsoleteBcd => GOTO obsoleteBcd;
          CompilerSmashedBcd => GOTO compilerSmashedBcd;
	  ANY => GOTO processingError];
    IF symFile # NIL THEN
      IncludesSymTables.LoadSymTables[
        symFile, symSegBase, symSegSize 
          ! IncludesSymTables.ObsoleteSymbolTable => GOTO obsoleteBcd]
    ELSE --no symbols-- 
      IF ~tableCompiled THEN GOTO ignoreBcd;
    WriteString["  "L];  WriteString[fileName];  WriteLine[".bcd"L];
    fe ← FileLists.InsertInFileList[fileName];
    feb[fe].stamp ← bcdVersion;
    feb[fe].bcdSourceTime ← bcdSourceTime;
    feb[fe].notAlto ← notAlto;
    feb[fe].crossJumped ← crossJumped;
    feb[fe].longAlto ← longAlto;
    feb[fe].tableCompiled ← tableCompiled;
    IF defModule THEN feb[fe].depth ← 50 + (feb[fe].depth MOD 50);
    -- if defs file was included by another defs file
    IF symFile # NIL THEN
      BEGIN
      ProcessIncludedFiles[fe, fileName ! ErroneousBcd => GOTO erroneousBcd];
      IncludesSymTables.ReleaseSymTables[];
      IF symFile # bcdFile THEN UnlockFile[symFile];
      END;
    EXITS
      ignoreBcd => NULL;
      obsoleteBcd =>
	BEGIN
	WriteString["  "L];
	WriteString[fileName];
	WriteLine[".bcd   -- compiled by an obsolete compiler"L];
	fe ← FileLists.InsertInFileList[fileName];
	feb[fe].obsolete ← TRUE;
	END;
      compilerSmashedBcd =>
	BEGIN
	WriteString["  "L];
	WriteString[fileName];
	WriteLine["  -- Bcd was marked invalid due to compilation errors"L];
	fe ← FileLists.InsertInFileList[fileName];
	feb[fe].erroneous ← TRUE;
	END;
      processingError =>
	BEGIN
	WriteString["  "L];
	WriteString[fileName];
	WriteLine["  -- Processing error"L];
	END;
      erroneousBcd =>
	BEGIN
	WriteLine["    -- invalid Bcd"L];
        IncludesSymTables.ReleaseSymTables[];
	IF symFile # bcdFile THEN UnlockFile[symFile];
	END;
    END;
    END;
    
  ExamineBcd: PROC [bcdFile: FileHandle]
    RETURNS [
      bcdVersion: BcdDefs.VersionStamp, bcdSourceTime: LONG CARDINAL,
      symFile: FileHandle, symSegBase, symSegSize: AltoDefs.PageNumber,
      defModule, notAlto, crossJumped, longAlto, tableCompiled: BOOLEAN] =
    BEGIN
    bcd: POINTER TO BcdDefs.BCD;
    bcdPages: AltoDefs.PageCount;
    mtb: BcdDefs.Base;
    mti: BcdDefs.MTIndex = FIRST[BcdDefs.MTIndex];
    bcdseg: FileSegmentHandle ← NewFileSegment[bcdFile, 1, 1, Read];
    
    CleanUp: PROC = 
      {Unlock[bcdseg];  DeleteFileSegment[bcdseg]};
      
    SwapIn[bcdseg];
    bcd ← FileSegmentAddress[bcdseg];
    IF (bcdPages ← bcd.nPages) # 1 THEN
      BEGIN
      Unlock[bcdseg];
      MoveFileSegment[bcdseg, 1, bcdPages];
      SwapIn[bcdseg];
      bcd ← FileSegmentAddress[bcdseg];
      END;
    IF bcd.versionIdent # BcdDefs.VersionID THEN
      IF bcd.versionIdent = FileLists.NullStamp.time THEN
	ERROR CompilerSmashedBcd[ ! UNWIND => CleanUp[]]
      ELSE ERROR ObsoleteBcd[ ! UNWIND => CleanUp[]];
    IF bcd.nConfigs # 0 THEN ERROR NotCompilerBcd[ ! UNWIND => CleanUp[]];
    mtb ← LOOPHOLE[bcd + bcd.mtOffset];
    bcdVersion ← bcd.version;
    bcdSourceTime ← bcd.sourceVersion.time;
    defModule ← bcd.definitions;
    tableCompiled ← bcd.tableCompiled;
    notAlto ← ~mtb[mti].altoCode;
    crossJumped ← mtb[mti].crossJumped;
    longAlto ← mtb[mti].long AND mtb[mti].altoCode;
    [symFile, symSegBase, symSegSize] ← FindSeg[
      bcdseg, mtb[mti].sseg ! UNWIND => CleanUp[]];
    CleanUp[];
    END;
    
  FindSeg: PROC [
      bcdSeg: FileSegmentHandle, sgi: BcdDefs.SGIndex]
      RETURNS [segFile: FileHandle, segBase, segSize: AltoDefs.PageNumber] =
    BEGIN OPEN String;
    bcd: POINTER TO BcdDefs.BCD ← FileSegmentAddress[bcdSeg];
    segHandle: BcdOps.SGHandle ← 
      @LOOPHOLE[bcd + bcd.sgOffset, BcdDefs.Base][sgi];
    IF segHandle.file = BcdDefs.FTNull THEN {segFile ← NIL; segBase ← 0}
    ELSE
      BEGIN
      IF segHandle.file = BcdDefs.FTSelf THEN segFile ← bcdSeg.file
      ELSE
	BEGIN
	f: BcdOps.FTHandle = @LOOPHOLE[bcd + bcd.ftOffset, BcdDefs.Base][
	  segHandle.file];
	ssb: BcdOps.NameString ← LOOPHOLE[bcd + bcd.ssOffset];
	ss: SubStringDescriptor ← [@ssb.string, f.name, ssb.size[f.name]];
	segFileName: STRING ← [AltoFileDefs.FilenameChars + 1];
	AppendSubString[segFileName, @ss];
	AddExtension[segFileName, ".bcd"];
	segFile ← NewFile[segFileName, DefaultAccess, DefaultVersion];
	LockFile[segFile];
	END;
      segBase ← segHandle.base;
      segSize ← segHandle.pages;
      END;
    END;
    
  AddExtension: PROC [name, ext: STRING] =
    BEGIN
    i: CARDINAL;
    FOR i IN [0..name.length) DO
      IF name[i] = '. THEN RETURN;
      ENDLOOP;
    String.AppendString[name, ext];
    END;
    
  ProcessIncludedFiles: PROC [includer: FileLists.FE, includerName: STRING] =
    BEGIN
    mdi: Symbols.MDIndex;
    includee: FileLists.FE;
    includeeName: STRING ← [AltoFileDefs.FilenameChars + 1];
    ss: String.SubStringDescriptor;
    i: CARDINAL;
    FOR mdi ← (FIRST[Symbols.MDIndex] + SIZE[Symbols.MDRecord]),
      (mdi + SIZE[Symbols.MDRecord]) UNTIL mdi >= IncludesSymTables.mdLimit DO
      SubStringForHash[@ss, IncludesSymTables.mdb[mdi].fileId];
      IF ss.length > (AltoFileDefs.FilenameChars + 1) THEN ERROR ErroneousBcd;
      includeeName.length ← 0;
      FOR i IN [0..ss.length) DO
	IF ss.base[ss.offset + i] = '. THEN EXIT;
	String.AppendChar[includeeName, ss.base[ss.offset + i]];
	ENDLOOP;
      includee ← FileLists.InsertInFileList[includeeName];
      feb[includer].includes ← FileLists.InsertIncludeFileItem[
	incList: feb[includer].includes, fe: includee, feName: includeeName,
	stamp: IncludesSymTables.mdb[mdi].stamp,
	fileOpenedByCompiler: 
	  (IncludesSymTables.mdb[mdi].file # Symbols.NullFileIndex)];
      IncreaseDepth[includee, (feb[includer].depth + 1)];
      feb[includee].includedBy ← FileLists.InsertIncludeFileItem[
	incList: feb[includee].includedBy, 
	fe: includer, feName: includerName, stamp: FileLists.NullStamp,
	fileOpenedByCompiler: FALSE];
      ENDLOOP;
    END;
    
  SubStringForHash: PROC [ss: String.SubString, hti: Symbols.HTIndex] =
    BEGIN
    ss.base ← IncludesSymTables.ssb;
    IF hti = Symbols.HTNull THEN ss.offset ← ss.length ← 0
    ELSE
      BEGIN
      ss.offset ← IncludesSymTables.ht[hti - 1].ssIndex;
      ss.length ← (IncludesSymTables.ht[hti].ssIndex - ss.offset);
      END;
    END;
    
  largestDepthCount: FileLists.InclusionDepth ← 0;
  
  IncreaseDepth: PROC [
      root: FileLists.FE, minDepth: FileLists.InclusionDepth] =
    BEGIN OPEN IODefs;
    i: FileLists.IncFile;
    includedFileDesc: FileLists.IncFileDesc;
    includedFile: FileLists.FE;
    IF feb[root].busy THEN
      BEGIN
      WriteString["     "L];
      WriteString[@feb[root].name];
      WriteLine[" is dependent upon a module that, in turn, depends upon it"L];
      RETURN;
      END;
    IF feb[root].depth >= minDepth THEN RETURN;
    feb[root].busy ← TRUE;
    largestDepthCount ← MAX[minDepth, largestDepthCount];
    feb[root].depth ← minDepth;
    FOR i ← feb[root].includes, ifb[i].link UNTIL i = FileLists.IFnil DO
      includedFileDesc ← ifb[i].includeFileDesc;
      includedFile ← ifdb[includedFileDesc].file;
      IncreaseDepth[includedFile, (minDepth + 1)];
      ENDLOOP;
    feb[root].busy ← FALSE;
    END;


 -- DISPLAY FILES WITH SOURCE BUT NO BCD ON DISK
    
  CheckForSourceButNoBcd: PROC =
    BEGIN OPEN IODefs;
    fe: FileLists.FE;
    firstTime: BOOLEAN ← TRUE;
    anyWritten: BOOLEAN ← FALSE;
    numOnLine: CARDINAL ← 0;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].source AND feb[fe].stamp = FileLists.NullStamp 
      AND ~(feb[fe].obsolete OR feb[fe].erroneous) 
      AND ~feb[fe].tableCompiled THEN
	BEGIN
	IF firstTime THEN
	  BEGIN
	  WriteChar[CR];
	  WriteString["The following source files have no Bcds on the disk:"L];
	  WriteChar[CR];
	  END;
	IF (numOnLine ← numOnLine + 1) > 4 THEN 
	  {WriteChar[CR]; numOnLine ← 1};
	WriteString["  "L];  WriteString[@feb[fe].name];
	WriteString[".mesa"L];
	firstTime ← FALSE;
	anyWritten ← TRUE;
	END;
      ENDLOOP;
    IF anyWritten THEN WriteChar[CR];
    END;


 -- MARK FILES THAT DIRECTLY (THEMSELVES) NEED RECOMPILATION
    
  badFilesExist: BOOLEAN ← FALSE;
  
  MarkDirectBads: PROC =
    BEGIN OPEN IODefs;
    fe: FileLists.FE;
    i: FileLists.IncFile;
    incFileDesc: FileLists.IncFileDesc;
    incStamp, diskStamp: BcdDefs.VersionStamp;
    ClearAllTags[]; -- prepare to tag files referenced in different versions
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      SELECT TRUE FROM
	feb[fe].obsolete, feb[fe].erroneous => MarkFileBad[fe];
	feb[fe].stamp # FileLists.NullStamp => -- bcd is on disk
	  BEGIN
	  IF feb[fe].source AND feb[fe].sourceTime # FileLists.NullTime 
	  AND feb[fe].bcdSourceTime # FileLists.NullTime 
	  AND feb[fe].sourceTime > feb[fe].bcdSourceTime THEN MarkFileBad[fe]
	  ELSE
	    FOR i ← feb[fe].includes, ifb[i].link UNTIL i = FileLists.IFnil DO
	      incFileDesc ← ifb[i].includeFileDesc;
	      incStamp ← ifdb[incFileDesc].stamp;
	      diskStamp ← feb[ifdb[incFileDesc].file].stamp;
	      IF incStamp # diskStamp AND incStamp # FileLists.NullStamp AND diskStamp #
		FileLists.NullStamp THEN
		BEGIN 
		MarkFileBad[fe];
		feb[ifdb[incFileDesc].file].tag ← TRUE; -- tag included file
		EXIT;
		END;
	      ENDLOOP;
	  END;
	feb[fe].source => -- source but no bcd on disk 
	  IF ~Switches[noCompIfNotOnDisk] AND ~feb[fe].tableCompiled THEN
	    MarkFileBad[fe];
	ENDCASE;
      ENDLOOP;
    ClearAllTags[];
    END;

  MarkFileBad: PROC [fe: FileLists.FE] = 
    {feb[fe].bad ← badFilesExist ← TRUE};
    
  ClearAllTags: PROC =
    BEGIN
    fe: FileLists.FE;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      feb[fe].tag ← FALSE ENDLOOP;
    END;

  PrintFilesInDifferentVersions: PROC =
    BEGIN OPEN IODefs;
    fe: FileLists.FE;
    firstTime: BOOLEAN ← TRUE;
    anyWritten: BOOLEAN ← FALSE;
    numOnLine: CARDINAL ← 0;
      
    PrintFile: PROC [fe: FileLists.FE] =
      BEGIN
      IF firstTime THEN
	BEGIN
	WriteChar[CR];
	WriteString[
	  "The following Bcds are included in a version different than that on disk:"L];
	WriteChar[CR];
	END;
      IF (numOnLine ← numOnLine + 1) >= 4 THEN {WriteChar[CR]; numOnLine ← 1};
      WriteString["  "L];
      WriteString[@feb[fe].name];
      WriteString[".bcd"L];
      firstTime ← FALSE;
      anyWritten ← TRUE;
      END;

    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].tag THEN PrintFile[fe];
      ENDLOOP;
    IF anyWritten THEN WriteChar[CR];
    END;

    
 -- OUTPUT COMPILATION ORDER, INCLUDE/INCLUDED BY RELATIONS, COMPILATION COMMAND
  
  DoOutput: PROC =
    BEGIN
    IF Switches[order] THEN -- print compilation order
      BEGIN
      IF Switches[multiple] THEN
	BEGIN OPEN String;
	s: STRING ← [AltoFileDefs.FilenameChars + 1];
	AppendChar[s, '.];
	AppendString[s, outputFileName];
	IF s[s.length] = '. THEN s.length ← s.length - 1;
	OutputDefs.OpenOutput["Source"L, s]
	END
      ELSE OutputDefs.OpenOutput[outputFileName, ".list"L];
      OutputCompileOrder[];
      END;
    IF Switches[includes] THEN -- print includes/included by relations
      BEGIN
      IF Switches[multiple] THEN
	BEGIN
	IF Switches[order] THEN OutputDefs.CloseOutput[];
	OutputDefs.OpenOutput[outputFileName, ".includes"L];
	END
      ELSE IF ~Switches[order] THEN 
	OutputDefs.OpenOutput[outputFileName, ".list"L];
      OutputIncludesRelation[];
      IF Switches[multiple] THEN
	BEGIN
	OutputDefs.CloseOutput[]; 
        OutputDefs.OpenOutput[outputFileName, ".includedBy"L];
	END
      ELSE OutputDefs.PutChar[IODefs.FF];
      OutputIncludedByRelation[];
      OutputDefs.CloseOutput[];
      END
    ELSE IF Switches[order] THEN OutputDefs.CloseOutput[];
    IF Switches[consistent] THEN -- put compilation command in Line.Cm
      BEGIN
      OutputDefs.OpenOutput["Line"L, ".cm"L];
      OutputCompilationCommand[];
      OutputDefs.CloseOutput[];
      END;
    END;

    
  OutputCompileOrder: PROC =
    BEGIN OPEN OutputDefs;
    currentDepth, nextLargestDepth: FileLists.InclusionDepth;
    
    OutputFilesOfDepth: PROC [depth: FileLists.InclusionDepth] =
      BEGIN
      fe: FileLists.FE;
      numOnLine: CARDINAL;
      PutString["  "L];
      nextLargestDepth ← numOnLine ← 0;
      FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
	IF ~feb[fe].tag THEN
	  IF feb[fe].depth = depth THEN
	    BEGIN 
	    IF (numOnLine ← numOnLine + 1) > 6 THEN
	      {PutCR[]; PutString["    "L]; numOnLine ← 1};
	    PutString[@feb[fe].name];
	    PutChar[IODefs.SP];
	    feb[fe].tag ← TRUE; 
	    END
	  ELSE nextLargestDepth ← MAX[feb[fe].depth, nextLargestDepth];
	ENDLOOP;
      PutCR[];
      END;
      
    PutString["Compilation Order (by inclusion depth):"L];
    PutCR[];
    ClearAllTags[];
    currentDepth ← largestDepthCount;
    WHILE currentDepth > 0 DO
      OutputFilesOfDepth[currentDepth]; currentDepth ← nextLargestDepth;
      ENDLOOP;
    ClearAllTags[];
    PutCR[];
    END;

    
  OutputIncludesRelation: PROC =
    BEGIN OPEN OutputDefs;
    fe: FileLists.FE;
    compilationSourceTimeOutput: BOOLEAN;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      compilationSourceTimeOutput ← FALSE;
      SELECT TRUE FROM
	feb[fe].obsolete => PrintObsoleteFile[fe];
	feb[fe].erroneous => PrintErroneousFile[fe];
	feb[fe].stamp # FileLists.NullStamp => -- bcd is on disk
	  BEGIN
	  PutFileName[fe, printStamp, 0];
	  IF feb[fe].bcdSourceTime # FileLists.NullStamp.time THEN
	    BEGIN
	    PutString[" (compilation source: "L];
	    PutTime[feb[fe].bcdSourceTime];
	    PutChar[')];
	    compilationSourceTimeOutput ← TRUE;
	    END;
	  IF feb[fe].source AND feb[fe].sourceTime # FileLists.NullStamp.time THEN
	    BEGIN
	    IF compilationSourceTimeOutput THEN {PutCR[]; PutString["    "L]}
	    ELSE PutChar[IODefs.SP];
	    IF feb[fe].bcdSourceTime # FileLists.NullStamp.time 
	    AND feb[fe].sourceTime > feb[fe].bcdSourceTime THEN PutChar['*];
	    PutString["(source on disk: "L];
	    IF feb[fe].bcdSourceTime # FileLists.NullStamp.time 
	    AND feb[fe].bcdSourceTime = feb[fe].sourceTime THEN
	      PutString["[same]"L]
	    ELSE PutTime[feb[fe].sourceTime];
	    PutChar[')];
	    END;
	  PutString[" includes"L];
	  IF feb[fe].includes = FileLists.IFnil THEN PutString[" nothing"L]
	  ELSE PrintIncludedFiles[fe];
	  PutCR[];  PutCR[];
	  END;
	ENDCASE;
      ENDLOOP;
    END;
    
  PrintObsoleteFile: PROC [fe: FileLists.FE] =
    BEGIN OPEN OutputDefs;
    PutChar['*];
    PutFileName[fe, noStamp, 0];
    PutString[" was compiled by an obsolete version of the compiler"L];
    PutCR[];  PutCR[];
    END;
    
  PrintErroneousFile: PROC [fe: FileLists.FE] =
    BEGIN OPEN OutputDefs;
    PutChar['*];
    PutFileName[fe, noStamp, 0];
    PutString[" was marked invalid because of compilation errors"L];
    PutCR[];  PutCR[];
    END;
    
  PrintIncludedFiles: PROC [fe: FileLists.FE] =
    BEGIN OPEN OutputDefs;
    i: FileLists.IncFile;
    FOR i ← feb[fe].includes, ifb[i].link UNTIL i = FileLists.IFnil DO
      BEGIN
      incFileDesc: FileLists.IncFileDesc = ifb[i].includeFileDesc;
      incStamp: BcdDefs.VersionStamp = ifdb[incFileDesc].stamp;
      incFile: FileLists.FE = ifdb[incFileDesc].file;
      incBad: BOOLEAN = 
        incStamp # feb[incFile].stamp 
	AND feb[incFile].stamp # FileLists.NullStamp;
      PutCR[];
      PutChar[IODefs.SP];
      PutChar[IF incBad THEN '* ELSE IODefs.SP];
      PutFileName[incFile, printStamp, 0];
      IF incBad THEN
	BEGIN
	PutString[", but version included was ("L];
	PutStamp[incStamp];
	PutChar[')];
	END
      ELSE IF incStamp = FileLists.NullStamp THEN 
	PutString[" ** never referenced"L];
      END;
    ENDLOOP;
    END;
    
  PutStamp: PROC [s: BcdDefs.VersionStamp] =
    BEGIN OPEN OutputDefs;
    PutTime[s.time];
    PutChar[IODefs.SP];
    PutNumber[s.net, [8, FALSE, FALSE, 1]];
    PutChar['#];
    PutNumber[s.host, [8, FALSE, FALSE, 1]];
    PutChar['#];
    END;
    
  PutFileName: PROC [
      fe: FileLists.FE, stampFlag: {printStamp, noStamp}, padLen: CARDINAL] =
    BEGIN OPEN OutputDefs;
    PutString[@feb[fe].name];
    IF padLen # 0 THEN
      BEGIN
      IF feb[fe].name.length < padLen THEN
	THROUGH [0..(padLen - feb[fe].name.length)) DO 
          PutChar[IODefs.SP];
          ENDLOOP
      ELSE PutChar[IODefs.SP];
      END;
    IF stampFlag = printStamp THEN
      IF feb[fe].stamp.time # FileLists.NullStamp.time THEN
	{PutString[" ("L]; PutStamp[feb[fe].stamp]; PutChar[')]};
    END;

    
  OutputIncludedByRelation: PROC =
    BEGIN OPEN OutputDefs;
    fe, incByFile: FileLists.FE;
    i: FileLists.IncFile;
    incFileDesc: FileLists.IncFileDesc;
    lhs: BOOLEAN;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].stamp # FileLists.NullStamp 
      OR (feb[fe].obsolete OR feb[fe].erroneous) THEN
	BEGIN
	PutFileName[fe, noStamp, 0];
	PutString[" is included by"L];
	IF feb[fe].includedBy = FileLists.IFnil THEN PutString[" nothing"L]
	ELSE
	  BEGIN
	  lhs ← TRUE;
	  FOR i ← feb[fe].includedBy, ifb[i].link UNTIL i = FileLists.IFnil DO
	    incFileDesc ← ifb[i].includeFileDesc;
	    incByFile ← ifdb[incFileDesc].file;
	    IF lhs THEN
	      {PutCR[]; PutString["  "L]; PutFileName[incByFile, noStamp, 22]}
	    ELSE PutFileName[incByFile, noStamp, 0];
	    lhs ← ~lhs;
	    ENDLOOP;
	  END;
	PutCR[];  PutCR[];
	END;
      ENDLOOP;
    END;

    
  nextLargestBadDepth: FileLists.InclusionDepth ← 0;
  lastFileCompiledHadSwitch: BOOLEAN ← FALSE;
  numOnLine: CARDINAL;
  
  OutputCompilationCommand: PROC =
    BEGIN
    badDepth: FileLists.InclusionDepth;
    fe: FileLists.FE;
    IF badFilesExist THEN
      BEGIN
      ExtendBadMarks[]; -- mark bad all files depending on directly bad files
      IODefs.WriteChar[IODefs.CR];
      IODefs.WriteLine["The following compilation command was written to Line.cm:"L];
      IODefs.WriteChar[IODefs.CR];
      OutputDefs.PutString["Compile"L];  
      IODefs.WriteString["  Compile"L];
      numOnLine ← 0;
      ClearAllTags[];
      badDepth ← 0;
      FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
	IF feb[fe].bad THEN badDepth ← MAX[feb[fe].depth, badDepth]; 
        ENDLOOP;
      WHILE badDepth > 0 DO
	CompileBadFilesOfDepth[badDepth];
	IF Switches[pause] AND nextLargestBadDepth > 0 THEN
	  BEGIN
	  OutputDefs.PutString[IF lastFileCompiledHadSwitch THEN "p"L ELSE "/p"L];
	  IODefs.WriteString[IF lastFileCompiledHadSwitch THEN "p"L ELSE "/p"L];
	  END;
	badDepth ← nextLargestBadDepth;
	ENDLOOP;
      ClearAllTags[];
      OutputDefs.PutCR[];  OutputDefs.PutCR[];
      IODefs.WriteChar[IODefs.CR];  IODefs.WriteChar[IODefs.CR];
      ListNeededFiles[];
      END
    ELSE 
      BEGIN
      OutputDefs.PutString["// The files are consistent"L];
      OutputDefs.PutCR[];
      IODefs.WriteChar[IODefs.CR];
      IODefs.WriteLine["The files are consistent"L];
      END;
    END;
    
  ExtendBadMarks: PROC =
    BEGIN
    fe: FileLists.FE;
    
    MarkBad: PROC [fe: FileLists.FE] =
      BEGIN
      i: FileLists.IncFile;
      incFileDesc: FileLists.IncFileDesc;
      IF feb[fe].tag THEN RETURN; -- fe & includers already marked bad
      IF CheckCycle[fe] THEN RETURN;
      feb[fe].busy ← TRUE;
      FOR i ← feb[fe].includedBy, ifb[i].link UNTIL i = FileLists.IFnil DO
	incFileDesc ← ifb[i].includeFileDesc;
	MarkBad[ifdb[incFileDesc].file];
	ENDLOOP;
      feb[fe].bad ← TRUE;
      feb[fe].tag ← TRUE;
      feb[fe].busy ← FALSE;
      END;
      
    ClearAllTags[];
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].bad THEN MarkBad[fe]; 
      ENDLOOP;
    ClearAllTags[];
    END;
    
  CheckCycle: PROC [fe: FileLists.FE] RETURNS [BOOLEAN] =
    BEGIN OPEN OutputDefs;
    IF feb[fe].busy THEN
      BEGIN
      PutCR[];
      PutString["-- "L];
      PutString[@feb[fe].name];
      PutString[" is dependent upon a module that, in turn, depends upon it"L];
      PutCR[];
      END;
    RETURN[feb[fe].busy];
    END;
    
  CompileBadFilesOfDepth: PROC [depth: FileLists.InclusionDepth] =
    BEGIN
    fe: FileLists.FE;
    nextLargestBadDepth ← 0;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].bad AND ~feb[fe].tag THEN
	IF feb[fe].depth = depth THEN
	  BEGIN 
	  lastFileCompiledHadSwitch ← FALSE;
	  OutputDefs.PutChar[IODefs.SP];  
	  OutputDefs.PutString[@feb[fe].name];
	  IF (numOnLine ← numOnLine + 1) > 5 THEN
	    BEGIN
	    IODefs.WriteChar[IODefs.CR];  IODefs.WriteString["    "L]; 
            numOnLine ← 1;
	    END
	  ELSE IODefs.WriteChar[IODefs.SP];
          IODefs.WriteString[@feb[fe].name];
	  IF feb[fe].notAlto OR feb[fe].crossJumped OR feb[fe].longAlto THEN
	    BEGIN
	    OutputDefs.PutChar['/];  IODefs.WriteChar['/];
	    IF feb[fe].notAlto THEN 
	      {OutputDefs.PutString["-a"L];  IODefs.WriteString["-a"L]};
	    IF feb[fe].crossJumped THEN
	      {OutputDefs.PutChar['j];  IODefs.WriteChar['j]};
	    IF feb[fe].longAlto THEN
	      {OutputDefs.PutChar['l];  IODefs.WriteChar['l]};
	    lastFileCompiledHadSwitch ← TRUE;
	    END;
	  feb[fe].tag ← TRUE; 
	  END
	ELSE nextLargestBadDepth ← MAX[feb[fe].depth, nextLargestBadDepth];
      ENDLOOP;
    END;
    
  ListNeededFiles: PROC =
    BEGIN
    TagNeededFilesNotOnDisk[];
    ListNeededSourceFiles[];
    ListNeededBcdFiles[];
    END;
    
  TagNeededFilesNotOnDisk: PROC =
    BEGIN
    fe, incFile: FileLists.FE;
    i: FileLists.IncFile;
    incFileDesc: FileLists.IncFileDesc;
    
    CheckIfFileRequired: PROC [
        fp: POINTER TO AltoFileDefs.FP, dirName: STRING]
        RETURNS [stop: BOOLEAN] =
      BEGIN OPEN String;
      fe: FileLists.FE;
      name: STRING ← [AltoFileDefs.FilenameChars + 1];
      ext: STRING ← [AltoFileDefs.FilenameChars + 1];
      mesa, bcd: BOOLEAN ← FALSE;
      SplitFileName[wholename: dirName, name: name, ext: ext];
      IF EquivalentString[ext, "mesa"] THEN mesa ← TRUE
      ELSE IF EquivalentString[ext, "bcd"] THEN bcd ← TRUE ELSE RETURN[FALSE];
      FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
        IF feb[fe].tag AND EquivalentString[@feb[fe].name, name] THEN
  	  BEGIN
  	  IF (bcd AND ~feb[fe].bad) OR (mesa AND feb[fe].bad) THEN
  	    {feb[fe].tag ← FALSE; EXIT};
  	  END;
        ENDLOOP;
      RETURN[FALSE]
      END;
      
    ClearAllTags[];
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].bad THEN
	BEGIN -- tag all files needed to compile "bad" file fe         
	FOR i ← feb[fe].includes, ifb[i].link UNTIL i = IFnil DO
	  IF ifb[i].fileOpenedByCompiler THEN
	    BEGIN
	    incFileDesc ← ifb[i].includeFileDesc;
	    incFile ← ifdb[incFileDesc].file;
	    feb[incFile].tag ← TRUE;
	    END;
	  ENDLOOP;
	feb[fe].tag ← TRUE;
	END;
      ENDLOOP;
    -- Remove tags if (not bad) bcd or mesa source exists.
    DirectoryDefs.EnumerateDirectory[CheckIfFileRequired];
    END;
    
  ListNeededSourceFiles: PROC =
    BEGIN
    fe: FileLists.FE;
    firstTime: BOOLEAN ← TRUE;  
    anyWritten: BOOLEAN ← FALSE;  
    numOnLine: CARDINAL ← 0;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF ~feb[fe].source AND (feb[fe].tag AND feb[fe].bad) THEN
	BEGIN -- by def. of tag, source not on disk
	IF firstTime THEN
	  BEGIN
	  OutputDefs.PutString["// Source files needed for the compilation which are not on the disk:"L];
	  OutputDefs.PutCR[];
	  OutputDefs.PutString["//   "L];
	  IODefs.WriteLine["The following source files needed for the compilation are not on the disk:"L];
	  IODefs.WriteString["  "L];
	  firstTime ← FALSE;
	  END;
	IF (numOnLine ← numOnLine + 1) > 4 THEN
	  BEGIN
	  OutputDefs.PutCR[];  OutputDefs.PutString["//   "L]; 
	  IODefs.WriteChar[IODefs.CR];  IODefs.WriteString["  "L]; 
          numOnLine ← 1;
	  END;
	OutputDefs.PutString[@feb[fe].name];  OutputDefs.PutString[".mesa"L];
        OutputDefs.PutString["  "L];
	IODefs.WriteString[@feb[fe].name];  IODefs.WriteString[".mesa"L];
        IODefs.WriteString["  "L];
	anyWritten ← TRUE;
	feb[fe].tag ← FALSE;
	END;
      ENDLOOP;
    IF anyWritten THEN {OutputDefs.PutCR[];  IODefs.WriteChar[IODefs.CR]};
    END;

  ListNeededBcdFiles: PROC =
    BEGIN
    fe: FileLists.FE;
    firstTime: BOOLEAN ← TRUE;  
    anyWritten: BOOLEAN ← FALSE;  
    numOnLine: CARDINAL ← 0;
    FOR fe ← FileLists.fileList, feb[fe].link UNTIL fe = FileLists.FEnil DO
      IF feb[fe].tag --AND NOT feb[fe].bad-- THEN
	BEGIN -- by def. of tag, bcd not on disk
	IF firstTime THEN
	  BEGIN
	  OutputDefs.PutCR[];
	  OutputDefs.PutString["// Bcd files needed for the compilation which are not on the disk:"L];
	  OutputDefs.PutCR[];
	  OutputDefs.PutString["//   "L];
	  IODefs.WriteChar[IODefs.CR]; 
	  IODefs.WriteLine["The following Bcds needed for the compilation are not on the disk:"L];
	  IODefs.WriteString["  "L];
	  firstTime ← FALSE;
	  END;
	IF (numOnLine ← numOnLine + 1) > 4 THEN
	  BEGIN
	  OutputDefs.PutCR[];  OutputDefs.PutString["//   "L]; 
	  IODefs.WriteChar[IODefs.CR];  IODefs.WriteString["  "L]; 
          numOnLine ← 1;
	  END;
	OutputDefs.PutString[@feb[fe].name];  OutputDefs.PutString[".bcd"L];
        OutputDefs.PutString["  "L];
	IODefs.WriteString[@feb[fe].name];  IODefs.WriteString[".bcd"L];
        IODefs.WriteString["  "L];
	anyWritten ← TRUE;
	feb[fe].tag ← FALSE;
	END;
      ENDLOOP;
    IF anyWritten THEN {OutputDefs.PutCR[];  IODefs.WriteChar[IODefs.CR]};
    END;

    
 -- MAIN BODY CODE
  
  BEGIN OPEN IODefs;
  ENABLE
    BEGIN
    FileLists.EnlargingTables =>
      {IncludesSymTables.UnlockSymFileSegments[]; RESUME};
    FileLists.DoneEnlargingTables =>
      {IncludesSymTables.ReloadSymFileSegments[]; RESUME};
    END;
  Initialize[];
  AddUserSpecifiedFiles[];
  CheckForSourceButNoBcd[];
  MarkDirectBads[];
  DoOutput[];
  Finalize[];
  ImageDefs.StopMesa[];
  END;
  END.