-- Install.Mesa  Edited by:
  -- Smokey on Apr 24, 1980 10:38 AM
  -- Bruce on July 10, 1980  11:27 AM
  -- Mark on Apr 16, 1980 8:43 PM
  -- PK on May 19, 1980 7:16 PM
  -- Sandman on July 11, 1980  10:32 AM

DIRECTORY
  Ascii USING [CR, NUL],
  BFSDefs USING [ActOnPages, GetNextDA, MakeCFP],
  Commands USING [GetToken, WriteCommand, WriteError],
  CompilerUtil USING [debug, error, parse, TableId],
  CoreSwapDefs USING [BBArray, BBHandle, CFP, ExternalStateVector, PuntInfo, PuntTable, SVPointer, SwapReason, UserBreakBlock, VersionID],
  Cursor USING [Set],
  DebugOps USING [Abort],
  DebugUsefulDefs USING [],
  DiskDefs USING [DiskRequest, RealDA],
  DOutput USING [Char, EOL, Line, Text],
  DSyms USING [Initialize],
  FileSW USING [Create, SetFile],
  FrameDefs USING [MakeCodeResident, UnNew],
  FrameOps USING [CodeHandle, MyGlobalFrame],
  Heap USING [Initialize],
  ImageDefs USING [AddFileRequest, FileRequest, StopMesa],
  Init USING [Adjust, CommandTab, DebugTab, DIGrammar, DumpCold, DumpHot, Files, InitialLocked, ourBitmapSeg, PcHot, SourceWindow, StartDebugger, UtilsHot, WriteHerald],
  Internal USING [Catcher, GetDebuggerNub, Interrupt, PauseAtDebuggerNub, ProcessBreakpoint, ShowBreak, ShowInterrupt, ShowSignal, SVPointer, SwatBreak],
  LoadStateOps USING [state],
  MachineDefs USING [BytesPerPage, CFP, eofDA, FA, FileHandle, fillinDA, GFHandle, NullGF, vDA],
  Menu USING [SetFont],
  MiscDefs USING [DestroyFakeModule, SetBlock],
  Nub USING [BadFile, BadVersion, InitSwitches, LoadNew, ProcessSwitches, Sob, Switches],
  NubOps USING [Place],
  NucleusOps USING [Wart],
  SDDefs USING [sBreakBlock, sBreakBlockSize, sCallDebugger, SD, sInterrupt, sProcessBreakpoint, sUncaughtSignal],
  SegmentDefs USING [Append, CopyDataToFileSegment, CopyFileToDataSegment, DataSegmentAddress, DataSegmentHandle, DefaultBase, DefaultVersion, DefaultXMBase, DeleteDataSegment, DeleteFileSegment, EnumerateFileSegments, FileHandle, FileSegmentHandle, GetEndOfFile, GetFileSegmentDA, InsufficientVM, LockFile, LongDataSegmentAddress, memConfig, NewDataSegment, NewFile, NewFileSegment, PageNumber, Read, ReadWriteAppend, ReleaseFile, SetEndOfFile, SetFileAccess, SetFileSegmentDA, UnlockFile, Write],
  State USING [GetSet, Go, GSHandle, OnYourMark],
  Storage USING [CopyString, FreeString, Node, PagesForWords],
  StreamDefs USING [CreateByteStream, DiskHandle, GetFA, JumpToFA, Read, StreamHandle],
  StringDefs USING [AppendChar, AppendString, EquivalentString],
  SwapperOps USING [MoveCode, systemTable],
  TajoMisc USING [SetBitmap],
  TajoOps USING [StartStimulusLevel],
  TextSW USING [SetEOF],
  ToolFont USING [Create],
  ToolWindow USING [Create, CreateSubwindow, Handle, SetName, Show, State],
  UserInput USING [CreateIndirectStringInOut, FunctionKeysetPNR, GetDefaultWindow, SetCursorPNR, SetKeyPNR, TypeInCursorPNR, TypeInPNR],
  UserTerminal USING [SetBackground, SetState, State],
  UserTerminalOps USING [SetBitmapSpace, StartUserTerminal],
  Window USING [Handle, Place],
  WindowFont USING [Handle, SetDefault];

Install: PROGRAM [PROGRAM]
  IMPORTS BFSDefs, Commands, Cursor, DebugOps,
    DiskDefs, DOutput, DSyms, FileSW, FrameDefs, FrameOps, Heap, ImageDefs, Init,
    Internal, LoadStateOps, Menu, MiscDefs, Nub, NucleusOps,
    SegmentDefs, State, Storage, StreamDefs, StringDefs, SwapperOps, 
    TextSW, ToolFont, TajoMisc, TajoOps, ToolWindow,
    UserInput, UserTerminal, UserTerminalOps, WindowFont
  EXPORTS CompilerUtil, DebugOps, DebugUsefulDefs, Init, TajoMisc =
  BEGIN OPEN MachineDefs;
  
  window: PUBLIC Window.Handle;
  fileSW: PUBLIC Window.Handle;
  myPlace: PUBLIC NubOps.Place ← debugger;
  initialToolStateDefault: PUBLIC ToolWindow.State ← inactive;
  displayOn: BOOLEAN ← FALSE;

  TableSegment: PUBLIC PROCEDURE [id: CompilerUtil.TableId]
      RETURNS [seg: SegmentDefs.FileSegmentHandle] =
    BEGIN OPEN CompilerUtil, Init;
    offset: CARDINAL;
    [seg, offset] ← MiscDefs.DestroyFakeModule[SELECT id FROM
	parse => LOOPHOLE[DIGrammar],
	error => LOOPHOLE[CommandTab],
	debug => LOOPHOLE[DebugTab],
	ENDCASE => ERROR];
    IF offset # 0 THEN ERROR;
    RETURN[seg];
    END;

  puntData: CoreSwapDefs.PuntTable;
  fa: FA;
  switches: Nub.Switches;
  data: State.GSHandle;

  FileRequest: TYPE = ImageDefs.FileRequest;

  ComCmFR, DebuggerFR, CoreFR, SwatFR, DebugDebuggerFR: FileRequest;
  MesaFontFR, SysFontFR, RemCmFR: FileRequest;
  DebugLogFR, InternalLogFR: FileRequest;

  Done: SIGNAL = CODE;
  
  SetSwappableSD: PROCEDURE =
    BEGIN OPEN Internal, SDDefs;
    sd: POINTER TO ARRAY [0..0) OF UNSPECIFIED = SD;
    sd[sProcessBreakpoint] ← ProcessBreakpoint;
    sd[sUncaughtSignal] ← Catcher;
    sd[sInterrupt] ← Interrupt;
    sd[sCallDebugger] ← PauseAtDebuggerNub;
    END;

  SetNonSwappableSD: PROCEDURE =
    BEGIN OPEN Internal, SDDefs;
    sd: POINTER TO ARRAY [0..0) OF UNSPECIFIED = SD;
    sd[sProcessBreakpoint] ← ShowBreak;
    sd[sUncaughtSignal] ← ShowSignal;
    sd[sInterrupt] ← ShowInterrupt;
    sd[sCallDebugger] ← GetDebuggerNub;
    END;

  NumberBlocks: CARDINAL = 5;

  InitBreakBlocks: PUBLIC PROCEDURE =
    BEGIN OPEN CoreSwapDefs, SDDefs;
    sd: POINTER TO ARRAY [0..0) OF UNSPECIFIED ← SD;
    size: CARDINAL = SIZE[UserBreakBlock]*NumberBlocks+SIZE[BBArray];
    p: BBHandle ← Storage.Node[size];
    p.length ← 0;
    sd[sBreakBlock] ← p;
    sd[sBreakBlockSize] ← size;
    RETURN
    END;

  RequestFiles: PROCEDURE =
    BEGIN OPEN SegmentDefs, Storage;
    ComCmFR ← [file: NIL, link:, access: Read, name: CopyString["Com.Cm."L]];
    DebuggerFR ←
      [file: NIL, link:, access: Read, name: CopyString["MesaDebugger."L]];
    CoreFR ← [file: NIL, link:, access: Read, name: CopyString["MesaCore."L]];
    SwatFR ← [file: NIL, link:, access: Read, name: CopyString["Swatee."L]];
    DebugDebuggerFR ← [file: NIL, link:, access: Read,
      name: CopyString["MesaDebugDebugger."L]];
    MesaFontFR ← [file: NIL, link:, access: Read,
      name: CopyString["MesaFont.strike."L]];
    SysFontFR ← [file: NIL, link:, access: Read,
      name: CopyString["SysFont.strike."L]];
    RemCmFR ← [file: NIL, link:, access: Read+Write+Append,
      name: CopyString["Rem.cm."L]];
    DebugLogFR ← [file: NIL, link:, access: Read+Write+Append,
      name: CopyString["Debug.log."L]];
    InternalLogFR ← [file: NIL, link:, access: Read+Write+Append,
      name: CopyString["InternalDebug.log."L]];
    ImageDefs.AddFileRequest[@DebuggerFR];
    ImageDefs.AddFileRequest[@CoreFR];
    ImageDefs.AddFileRequest[@SwatFR];
    ImageDefs.AddFileRequest[@DebugDebuggerFR];
    ImageDefs.AddFileRequest[@ComCmFR];
    ImageDefs.AddFileRequest[@MesaFontFR];
    ImageDefs.AddFileRequest[@SysFontFR];
    ImageDefs.AddFileRequest[@RemCmFR];
    ImageDefs.AddFileRequest[@DebugLogFR];
    ImageDefs.AddFileRequest[@InternalLogFR];
    END;

  FreeStrings: PROC =
    BEGIN
    Storage.FreeString[ComCmFR.name];
    Storage.FreeString[DebugDebuggerFR.name];
    Storage.FreeString[SwatFR.name];
    Storage.FreeString[CoreFR.name];
    Storage.FreeString[DebuggerFR.name];
    Storage.FreeString[MesaFontFR.name];
    Storage.FreeString[SysFontFR.name];
    Storage.FreeString[RemCmFR.name];
    Storage.FreeString[DebugLogFR.name];
    Storage.FreeString[InternalLogFR.name];
    END;

  DebugDebuggerInstall: PROCEDURE =
    BEGIN
    debuggee: SegmentDefs.FileHandle;
    myPlace ← internaldebugger;
    [data.selfFH, data.selfFP.leaderDA] ←
      FixFile[@DebugDebuggerFR, @data.selfFP];
    [debuggee, data.debuggeeFP.leaderDA] ←
      FixFile[@DebuggerFR, @data.debuggeeFP];
    data.debuggerFP ← data.selfFP;
    data.debuggeeFH ← debuggee;
    MoveLoadState[@DebugDebuggerFR];
    Init.Files[debuggee];
    SetupPuntESV[FALSE, NIL];
    SetNonSwappableSD[];
    ResetDebugScriptFile[];
    END;

  DebuggerInstall: PROCEDURE =
    BEGIN
    swappable: BOOLEAN ← FALSE;
    debuggee: SegmentDefs.FileHandle;
    IF InternalLogFR.file # NIL THEN
      SegmentDefs.ReleaseFile[InternalLogFR.file];
    [data.selfFH, data.selfFP.leaderDA] ←
      FixFile[@DebuggerFR, @data.selfFP];
    IF CoreFR.file # NIL THEN
      BEGIN
      [debuggee, data.debuggeeFP.leaderDA] ←
	FixFile[@CoreFR, @data.debuggeeFP];
      SegmentDefs.ReleaseFile[SwatFR.file];
      END
    ELSE [debuggee, data.debuggeeFP.leaderDA] ←
      FixFile[@SwatFR, @data.debuggeeFP];
    IF DebugDebuggerFR.file # NIL THEN
      BEGIN
      swappable ← TRUE;
      [, data.debuggerFP.leaderDA] ←
	FixFile[@DebugDebuggerFR, @data.debuggerFP];
      END;
    data.debuggeeFH ← debuggee;
    Init.Files[debuggee];
    SetupPuntESV[swappable, IF swappable THEN data.selfFH ELSE NIL];
    IF swappable THEN SetSwappableSD[] ELSE SetNonSwappableSD[];
    END;

  FixFile: PROCEDURE [fr: POINTER TO FileRequest, p: POINTER TO CFP]
      RETURNS [f: FileHandle, da: vDA] =
    BEGIN OPEN SegmentDefs;
    s: FileSegmentHandle;
    pages: PageNumber;
    bytes: CARDINAL;
    IF (f ← fr.file) = NIL THEN f ←
      NewFile[fr.name, Read+Write+Append, DefaultVersion]
    ELSE SetFileAccess[f, Read+Write+Append];
    LockFile[f];
    [pages, bytes] ← GetEndOfFile[f];
    IF pages < 255 OR (pages = 255 AND bytes < BytesPerPage) THEN
      SetEndOfFile[f, 255, BytesPerPage];
    s ← SegmentDefs.NewFileSegment[f,1,1,SegmentDefs.Read];
    BFSDefs.MakeCFP[p,@f.fp];
    da ← LOOPHOLE[DiskDefs.RealDA[SegmentDefs.GetFileSegmentDA[s]]];
    SegmentDefs.DeleteFileSegment[s];
    UnlockFile[f];
    RETURN[f, da];
    END;

  SetupPuntESV: PROCEDURE [swappable: BOOLEAN, file: FileHandle] =
    BEGIN
    seg: SegmentDefs.FileSegmentHandle ← LoadStateOps.state;
    puntData.puntESV.reason ← punt;
    puntData.puntESV.versionident ← CoreSwapDefs.VersionID;
    puntData.puntESV.tables ← @SwapperOps.systemTable;
    puntData.puntESV.drumFile ← file;
    puntData.puntESV.loadstateCFA.fp ← seg.file.fp;
    puntData.puntESV.loadstateCFA.fa ← [
      page: seg.base, byte: 0, da: SegmentDefs.GetFileSegmentDA[seg]];
    puntData.puntESV.lspages ← seg.pages;
    puntData.puntESV.bitmap ← NIL;
    puntData.puntESV.bitmapPages ← 0;
    IF swappable THEN
      BEGIN
      puntData.pDebuggerFP ← @data.debuggerFP;
      puntData.debuggerFP ← data.debuggerFP;
      puntData.pCoreFP ← @data.selfFP;
      puntData.coreFP ← data.selfFP;
      END
    ELSE puntData.pDebuggerFP ← puntData.pCoreFP ← LOOPHOLE[0];
    CoreSwapDefs.PuntInfo↑ ← @puntData;
    puntData.puntESV.fill ← ALL[0];
    END;

  MoveLoadState: PROCEDURE [fr: POINTER TO ImageDefs.FileRequest] =
    BEGIN OPEN SegmentDefs;
    f: FileHandle;
    new, old: FileSegmentHandle;
    temp: DataSegmentHandle;
    old ← LoadStateOps.state;
    IF (f ← fr.file) = NIL THEN f ← fr.file ←
      NewFile[fr.name, Read+Write+Append, DefaultVersion]
    ELSE SetFileAccess[f, Read+Write+Append];
    SetEndOfFile[f, 255+old.pages, BytesPerPage];
    temp ← NewDataSegment[DefaultBase, old.pages];
    new ← NewFileSegment[f, 256, old.pages, Read+Write];
    CopyFileToDataSegment[old, temp];
    CopyDataToFileSegment[temp, new];
    DeleteDataSegment[temp];
    DeleteFileSegment[old];
    LoadStateOps.state ← new;
    END;

  CollectDiskAddresses: PROCEDURE =
    BEGIN OPEN SegmentDefs;
    ImageFile: FileHandle =
      FrameOps.CodeHandle[FrameOps.MyGlobalFrame[]].file;
    DAs: DESCRIPTOR FOR ARRAY OF vDA;
    maxunknown, maxknown: CARDINAL ← FIRST[CARDINAL];
    minunknown: CARDINAL ← LAST[CARDINAL];
    maxknownDA: vDA;
    DisplayHead: POINTER TO WORD = LOOPHOLE[420B];
    DisplayInterruptWord: POINTER TO WORD = LOOPHOLE[421B];
    saveDisplay, saveDiw: WORD;
    diskrequest: DiskDefs.DiskRequest;
    bufseg, DAseg: DataSegmentHandle;
    FindEnds: PROCEDURE [seg: FileSegmentHandle] RETURNS [BOOLEAN] =
      BEGIN
      WITH s: seg SELECT FROM
	disk =>
	  IF s.file = ImageFile AND s.hint.da = eofDA THEN
	    BEGIN
	    maxunknown ← MAX[maxunknown,s.base];
	    minunknown ← MIN[minunknown,s.base];
	    END;
	ENDCASE;
      RETURN[FALSE];
      END;
    FindKnown: PROCEDURE [seg: FileSegmentHandle] RETURNS [BOOLEAN] =
      BEGIN
      WITH s: seg SELECT FROM
	disk =>
	  IF s.file = ImageFile AND s.hint.da # eofDA AND s.base < minunknown
	    AND s.base > maxknown THEN
	    BEGIN maxknown ← s.base; maxknownDA ← s.hint.da END;
	ENDCASE;
      RETURN[FALSE];
      END;
    PlugDA: PROCEDURE [seg: FileSegmentHandle] RETURNS [BOOLEAN] =
      BEGIN
      WITH s: seg SELECT FROM
	disk =>
	  IF s.file = ImageFile AND s.hint.da = eofDA AND
	    s.base IN (maxknown..maxunknown] THEN
	    SegmentDefs.SetFileSegmentDA[@s,DAs[s.base]];
	ENDCASE;
      RETURN[FALSE];
      END;

    saveDisplay ← DisplayHead↑;
    saveDiw ← DisplayInterruptWord↑;
    DisplayHead↑ ← DisplayInterruptWord↑ ← 0;
    [] ← EnumerateFileSegments[FindEnds];
    [] ← EnumerateFileSegments[FindKnown];
    bufseg ← NewDataSegment[DefaultBase, 1];
    DAseg ← NewDataSegment[
      DefaultBase, Storage.PagesForWords[maxunknown-maxknown+3]];
    DAs ← DESCRIPTOR[DataSegmentAddress[DAseg]-(maxknown-1),maxunknown+2];
    diskrequest ← DiskDefs.DiskRequest [
      ca: DataSegmentAddress[bufseg],
      fixedCA: TRUE,
      da: @DAs[0],
      fp: @ImageFile.fp,
      firstPage: maxknown,
      lastPage: maxunknown,
      action: ReadD,
      lastAction: ReadD,
      signalCheckError: FALSE,
      option: update[cleanup: BFSDefs.GetNextDA]];
    MiscDefs.SetBlock[@DAs[maxknown-1],fillinDA,maxunknown-maxknown+3];
    DAs[maxknown] ← maxknownDA;
    [] ← BFSDefs.ActOnPages[LOOPHOLE[@diskrequest]];  -- we know it is an Update diskrequest
    [] ← EnumerateFileSegments[PlugDA];
    DeleteDataSegment[DAseg];
    DeleteDataSegment[bufseg];
    DisplayHead↑ ← saveDisplay;
    DisplayInterruptWord↑ ← saveDiw;
    RETURN;
    END;

  LoadDebugger: PROCEDURE =
    BEGIN OPEN switches;
    SkipImage[];
    UNTIL install OR internalInstall DO
      DoCommand[ !
	Done => BEGIN install ← TRUE; CONTINUE END;
	ABORTED => CONTINUE;
	DebugOps.Abort => CONTINUE;
	Nub.BadFile =>
	  BEGIN
	  DOutput.EOL[];
	  Commands.WriteError[file];
	  DOutput.Text[file];
	  CONTINUE
	  END;
	Nub.BadVersion --[badname: STRING] --=> 
	  BEGIN
	  DOutput.EOL[];
	  Commands.WriteError[file];
	  DOutput.Text[badname];
	  Commands.WriteError[diffver];
	  RESUME
	  END];
      ENDLOOP;
    RETURN
    END;
  
  DoCommand: PROCEDURE =
    BEGIN
    f: GFHandle;
    p: PROCESS;
    f ← LoadSystem[];
    IF f # NullGF THEN
      BEGIN p ← FORK StartModule[LOOPHOLE[f]]; JOIN p; END;
    END;
  
  StartModule: PROCEDURE [f: PROGRAM] =
    BEGIN ENABLE ABORTED, DebugOps.Abort => CONTINUE;
    IF ~LOOPHOLE[f, GFHandle].started THEN START f ELSE RESTART f;
    RETURN
    END;
  
  CleanUpCommandLine: PROCEDURE =
    BEGIN
    SegmentDefs.UnlockFile[ComCmFR.file];
    SegmentDefs.ReleaseFile[ComCmFR.file];
    RETURN
    END;
  
  LoadSystem: PROCEDURE RETURNS [user: GFHandle] =
    BEGIN
    switches ← Nub.InitSwitches[];
    user ← LoadUser[@fa ! UNWIND => CleanUpCommandLine[]];
    IF ~switches.start THEN user ← NullGF;
    RETURN
    END;
  
  LoadUser: PROCEDURE [fa: POINTER TO FA]
    RETURNS [user: GFHandle] =
    BEGIN OPEN StreamDefs;
    com: StreamHandle;
    name: STRING ← [40];
    ext: STRING ← [10];
    sw: STRING ← [10];
    get: PROCEDURE RETURNS [c: CHARACTER] =
      BEGIN
      IF com.endof[com] THEN RETURN[Ascii.NUL];
      RETURN[com.get[com]];
      END;
    IF ComCmFR.file = NIL THEN SIGNAL Done;
    com ← CreateByteStream[ComCmFR.file, Read];
    user ← NullGF;
    BEGIN OPEN switches;
      StreamDefs.JumpToFA[com, fa ! ANY => GO TO finished];
      Commands.GetToken[get, name, ext, sw];
      IF name.length = 0 AND sw.length = 0 THEN GO TO finished;
      StreamDefs.GetFA[com, fa];
      com.destroy[com];
      DoSwitches[sw];
      IF name.length # 0 AND ~command THEN
	BEGIN
	IF ext.length = 0 THEN ext ← "bcd"L;
	DOutput.EOL[];
	DOutput.Char['/];
	DOutput.Text[name];
	IF sw.length # 0 THEN
	  BEGIN DOutput.Char['/]; DOutput.Text[sw] END;
	StringDefs.AppendChar[name, '.];
	StringDefs.AppendString[name, ext];
	IF ~displayOn THEN {displayOn ← TRUE; [] ← UserTerminal.SetState[on]};
	user ← Nub.LoadNew[name, framelinks];
	END;
      IF command THEN DoSwitches[name];
    EXITS
      finished => BEGIN com.destroy[com]; SIGNAL Done; END;
    END;
    RETURN
    END;
  
  SkipImage: PROCEDURE =
    BEGIN OPEN StreamDefs;
    com: StreamHandle;
    name: STRING ← [40];
    ext: STRING ← [10];
    sw: STRING ← [10];
    get: PROCEDURE RETURNS [c: CHARACTER] =
      BEGIN
      IF com.endof[com] THEN RETURN[Ascii.NUL];
      RETURN[com.get[com]];
      END;
    IF ComCmFR.file = NIL THEN RETURN;
    SegmentDefs.LockFile[ComCmFR.file];
    switches ← Nub.InitSwitches[];
    com ← CreateByteStream[ComCmFR.file, Read];
    StreamDefs.GetFA[com, @fa];
    Commands.GetToken[get, name, ext, sw];
    IF StringDefs.EquivalentString[ext, "image"L] THEN
      StreamDefs.GetFA[com, @fa];
    com.destroy[com];
    DoSwitches[sw];
    END;
  
  DoSwitches: PROC [s: STRING] =
    BEGIN
    old: Nub.Sob ← switches↑;
    Nub.ProcessSwitches[s];
    IF old # switches↑ AND ~displayOn THEN
      BEGIN displayOn ← TRUE; [] ← UserTerminal.SetState[on] END;
    IF old.trees # switches.trees THEN
      BEGIN
      Commands.WriteCommand[treePrinting];
      IF switches.trees THEN Commands.WriteCommand[on]
      ELSE Commands.WriteCommand[off];
      DOutput.Char[Ascii.CR];
      data.tree ← switches.trees;
      END;
    IF old.search # switches.search THEN
      BEGIN
      IF switches.search THEN Commands.WriteCommand[oneFrame]
      ELSE Commands.WriteCommand[callStack];
      DOutput.Char[Ascii.CR];
      data.search ← switches.search;
      END;
    IF old.display # switches.display THEN
      BEGIN
      DOutput.Line["Invert display."L];
      [] ← UserTerminal.SetBackground[
	IF switches.display THEN black ELSE white];
      END;
    END;

  ResetDebugScriptFile: PROCEDURE =
    BEGIN
    name: STRING = "InternalDebug.log"L;
    sh: StreamDefs.StreamHandle ← NIL;
    IF InternalLogFR.file # NIL THEN
      sh ← StreamDefs.CreateByteStream[
	InternalLogFR.file,SegmentDefs.ReadWriteAppend];
    ToolWindow.SetName[window, name];
    FileSW.SetFile[fileSW, name, sh];
    TextSW.SetEOF[fileSW, 0];
    ToolWindow.Show[window];
    END;
  
  InitDebugWindow: PROC =
    BEGIN
    name: STRING = "Debug.log"L;
    default: Window.Handle = UserInput.GetDefaultWindow[];
    sh: StreamDefs.StreamHandle ← NIL;
    window ← ToolWindow.Create[
      name, Init.Adjust, NIL, [[0,32], [512,320]]]; 
    fileSW ← ToolWindow.CreateSubwindow[
      window, LOOPHOLE[0], [[0,0], [400,400]], many];
    IF DebugLogFR.file # NIL THEN
      sh ← StreamDefs.CreateByteStream[
	DebugLogFR.file,SegmentDefs.ReadWriteAppend];
    FileSW.Create[fileSW, name, [append,TRUE,TRUE,TRUE,TRUE,FALSE,FALSE],sh];
    TextSW.SetEOF[fileSW, 0];
    UserInput.CreateIndirectStringInOut[from: default, to: fileSW];
    UserInput.SetKeyPNR[default, keyboard, UserInput.TypeInPNR];
    UserInput.SetKeyPNR[default, keyset, UserInput.FunctionKeysetPNR];
    UserInput.SetCursorPNR[default, UserInput.TypeInCursorPNR];
    ToolWindow.Show[window];
    END;

  FontFile: PROC RETURNS [file: SegmentDefs.FileHandle] =
    BEGIN OPEN SegmentDefs;
    NoFont: STRING = "// Can't install without strike font."L;
    sh: StreamDefs.DiskHandle;
    file ← IF MesaFontFR.file # NIL THEN MesaFontFR.file ELSE SysFontFR.file;
    IF file # NIL THEN {ReleaseFile[RemCmFR.file]; RETURN};
    sh ← StreamDefs.CreateByteStream[RemCmFR.file,Read+Write+Append];
    FOR i: CARDINAL IN [0..NoFont.length) DO sh.put[sh,NoFont[i]] ENDLOOP;
    sh.destroy[sh];
    ImageDefs.StopMesa[];
    END;

  addr: LONG POINTER ← NIL;
  seg: POINTER;
  xm: BOOLEAN;

  StartTools: PROC =
    BEGIN
    font: WindowFont.Handle;
    UserTerminalOps.StartUserTerminal[];
    TajoOps.StartStimulusLevel[];
    Init.ourBitmapSeg ← NIL;
    IF xm THEN 
      BEGIN OPEN SegmentDefs;
      Init.ourBitmapSeg ← NewDataSegment[DefaultXMBase,99 ! InsufficientVM => CONTINUE];
      seg ← Init.ourBitmapSeg;
      END;
    IF Init.ourBitmapSeg # NIL THEN 
      BEGIN
      addr ← SegmentDefs.LongDataSegmentAddress[Init.ourBitmapSeg];
      UserTerminalOps.SetBitmapSpace[address: addr, words: 99*256];
      TajoMisc.SetBitmap[[[32, 32], [544, 744]]];
      END
    ELSE TajoMisc.SetBitmap[[[48,72], [512,352]]];
    [] ← UserTerminal.SetBackground[white];
    [] ← UserTerminal.SetState[off];
    Cursor.Set[hourGlass];
    font ← ToolFont.Create[FontFile[]];
    WindowFont.SetDefault[font];
    Menu.SetFont[font];
    START Init.SourceWindow;
    InitDebugWindow[];
    END;
  
  -- Main body
  
  SetNonSwappableSD[];
  SDDefs.SD[SDDefs.sProcessBreakpoint] ← Internal.SwatBreak;
  InitBreakBlocks[];
  RequestFiles[];
  
  STOP;
  
  IF (xm ← SegmentDefs.memConfig.useXM) THEN {
    FrameDefs.MakeCodeResident[LOOPHOLE[Init.InitialLocked]];
    SwapperOps.MoveCode[intoMDS]}; 
  Heap.Initialize[];
  State.OnYourMark[];
  data ← State.GetSet[];
  switches ← Nub.InitSwitches[];
  CollectDiskAddresses[];
  FrameDefs.UnNew[LOOPHOLE[NucleusOps.Wart, GFHandle]];
  SDDefs.SD[SDDefs.sProcessBreakpoint] ← Internal.ShowBreak;
  
  StartTools[];
  State.Go[];
  Init.WriteHerald[TRUE];
  DSyms.Initialize[];
  START Init.PcHot;
  START Init.UtilsHot;
  START Init.DumpCold;
  START Init.DumpHot;

  LoadDebugger[ ! DebugOps.Abort => CONTINUE];
  IF switches.internalInstall THEN DebugDebuggerInstall[]
  ELSE DebuggerInstall[];
  FreeStrings[];
  initialToolStateDefault ← active;
  IF ~displayOn THEN {displayOn ← TRUE; [] ← UserTerminal.SetState[on]};
  Cursor.Set[textPointer];
  Init.StartDebugger[];
  ImageDefs.StopMesa[];

  END.