DIRECTORY Ascii USING [BS, ControlA, ControlQ, ControlW, ControlX, CR, DEL, Digit, Letter, SP], BasicTime USING [GMT, nullGMT, Period], Booting USING [RegisterProcs, RollbackProc, switches], DefaultRemoteNames USING [DefaultNames, Get], DFOperations USING [BringOver, ChoiceInteraction, ChoiceResponse, Choices, DFInfoInteraction, FileInteraction, InfoInteraction, InteractionProc, YesNoInteraction, YesNoResponse], DFUtilities USING [DateToRope], FS USING [Close, ComponentPositions, Copy, GetInfo, GetName, Error, ExpandName, Open, OpenFile, StreamOpen], FSPseudoServers USING [InsertPseudoServer, Lookup, PseudoServerFromRope, PseudoServerList], GermSwap USING [Switch], Idle USING [IdleHandler, IsIdle, RegisterIdleHandler], IO USING [Close, EndOfStream, Error, GetChar, GetTime, GetTokenRope, EraseChar, IDProc, PutChar, PutF, PutF1, PutFR, PutRope, STREAM], List USING [PutAssoc], Process USING [SecondsToTicks], ProcessProps USING [PushPropList], Rope USING [Cat, Concat, Equal, Fetch, FromChar, Length, ROPE, SkipTo, Substr], SimpleTerminal USING [InputTimeout, SetInputTimeout, TurnOff, TurnOn], SystemVersion USING [release], Terminal USING [BlinkBWDisplay, Current], UserCredentials USING [CredentialsChangeProc, Get, RegisterForChange], UserProfile USING [ProfileChanged, Token]; InstallerImpl: CEDAR PROGRAM IMPORTS Ascii, BasicTime, Booting, DefaultRemoteNames, DFOperations, DFUtilities, FS, FSPseudoServers, Idle, IO, List, Process, ProcessProps, Rope, SimpleTerminal, SystemVersion, Terminal, UserCredentials, UserProfile = BEGIN ROPE: TYPE = Rope.ROPE; in, out: IO.STREAM _ NIL; GetChoice: PROC [c: REF DFOperations.ChoiceInteraction] RETURNS [choice: NAT] = { DO default: ROPE = c.choices[choice _ c.default]; ans: ROPE _ NIL; firstChar: BOOL _ TRUE; FlushVisible: PROC = { r: ROPE = IF firstChar THEN default ELSE ans; FOR i: INT DECREASING IN [0..r.Length[]) DO out.EraseChar[r.Fetch[i]]; ENDLOOP; ans _ NIL; choice _ c.default; firstChar _ FALSE; }; THROUGH [0..2*depth) DO out.PutChar[Ascii.SP]; ENDLOOP; out.PutRope[c.message]; out.PutChar[Ascii.SP]; out.PutRope[default]; DO oldAns: ROPE = ans; char: CHAR; char _ in.GetChar[ ! SimpleTerminal.InputTimeout => {char _ Ascii.CR; CONTINUE}]; SELECT char FROM Ascii.DEL => {out.PutRope[" XXX\N"]; GO TO startOver}; Ascii.CR => IF ans.Length[] = 0 THEN GO TO done; Ascii.BS, Ascii.ControlA => IF firstChar THEN FlushVisible[] ELSE IF ans.Length[] > 0 THEN { out.EraseChar[ans.Fetch[ans.Length[]-1]]; ans _ ans.Substr[len: ans.Length[]-1]; }; Ascii.ControlQ, Ascii.ControlW, Ascii.ControlX => FlushVisible[]; '? => { out.PutRope[" XXX\NChoices are: "]; FOR i: NAT IN [0..c.choices.length) DO IF i ~= 0 THEN out.PutRope[", "]; out.PutRope[c.choices[i]]; ENDLOOP; out.PutChar[Ascii.CR]; IF c.explanations ~= NIL THEN FOR i: NAT IN [0..c.explanations.length) DO IF c.explanations[i] ~= NIL THEN { out.PutRope[c.explanations[i]]; out.PutChar[Ascii.CR]; }; ENDLOOP; GO TO startOver }; ENDCASE => { state: {notFound, found, ambiguous} _ notFound; IF firstChar THEN FlushVisible[]; ans _ ans.Concat[Rope.FromChar[char]]; FOR i: NAT IN [0..c.choices.length) DO IF ans.Equal[s2: c.choices[i].Substr[len: ans.Length[]], case: FALSE] THEN { IF ans.Length[] = c.choices[i].Length[] THEN {choice _ i; state _ found; EXIT}; SELECT state FROM notFound => {choice _ i; state _ found}; found => state _ ambiguous; ENDCASE; }; ENDLOOP; SELECT state FROM notFound => { Terminal.BlinkBWDisplay[Terminal.Current[]]; ans _ oldAns; }; found => { out.PutRope[c.choices[choice].Substr[start: oldAns.Length[]]]; GO TO done }; ambiguous => out.PutChar[c.choices[choice].Fetch[oldAns.Length[]]]; ENDCASE; }; REPEAT startOver => NULL; ENDLOOP; REPEAT done => NULL; ENDLOOP; out.PutChar[Ascii.CR]; }; Confirm: PROC [message: ROPE, default: BOOL _ TRUE] RETURNS [BOOL] = { c: REF DFOperations.ChoiceInteraction = NEW[DFOperations.ChoiceInteraction _ [ message: message, choices: yesNo, explanations: NIL, default: default.ORD ]]; OpenTerminal[]; RETURN[VAL[GetChoice[c]]] }; autoConfirm: BOOL _ TRUE; depth: INT _ -1; Interact: DFOperations.InteractionProc = { OpenTerminal[]; WITH interaction SELECT FROM info: REF DFOperations.InfoInteraction => { prompt: BOOL _ TRUE; THROUGH [0..2*depth) DO out.PutChar[Ascii.SP]; ENDLOOP; SELECT info.class FROM info => prompt _ FALSE; warning => out.PutRope["Warning: "]; error => out.PutRope["Error: "]; abort => NULL; ENDCASE; out.PutRope[info.message]; out.PutChar[Ascii.CR]; IF prompt THEN { IF Confirm["Shall I continue anyway?"] THEN RETURN; out.PutRope["Giving up..."]; Die[]; }; }; info: REF DFOperations.DFInfoInteraction => { SELECT info.action FROM start => { depth _ depth.SUCC; THROUGH [0..2*depth) DO out.PutChar[Ascii.SP]; ENDLOOP; out.PutRope["BringOver of "]; out.PutRope[info.dfFile]; }; end => { THROUGH [0..2*depth) DO out.PutChar[Ascii.SP]; ENDLOOP; out.PutRope["End BringOver of "]; out.PutRope[info.dfFile]; depth _ depth.PRED; }; abort => { out.PutRope["BringOver of "]; out.PutRope[info.dfFile]; out.PutRope[" aborted"]; depth _ -1; }; ENDCASE; IF info.message ~= NIL THEN IO.PutF1[out, " (%g)", [rope[info.message]]]; out.PutChar[Ascii.CR]; }; c: REF DFOperations.ChoiceInteraction => IF c.blunder OR ~autoConfirm THEN RETURN[response: NEW[DFOperations.ChoiceResponse _ [GetChoice[c]]]]; yn: REF DFOperations.YesNoInteraction => IF yn.blunder OR ~autoConfirm THEN { c: REF DFOperations.ChoiceInteraction = NEW[DFOperations.ChoiceInteraction _ [ message: yn.message, choices: ynqa, explanations: NIL, default: IF yn.default THEN YNQA.yes.ORD ELSE YNQA.no.ORD ]]; choice: YNQA = VAL[GetChoice[c]]; SELECT choice FROM $yes => RETURN[response: NEW[DFOperations.YesNoResponse _ [TRUE]]]; $no => RETURN[response: NEW[DFOperations.YesNoResponse _ [FALSE]]]; $quit => { abort _ TRUE; abortMessageForLog _ "(requested by user)"; }; $all => { autoConfirm _ TRUE; RETURN[response: NEW[DFOperations.YesNoResponse _ [TRUE]]] }; ENDCASE; }; file: REF DFOperations.FileInteraction => IF autoConfirm THEN { THROUGH [0..2*depth) DO out.PutChar[Ascii.SP]; ENDLOOP; IO.PutF[out, "%g %g %g {%g}%g\N", [rope[file.localFile]], [rope[SELECT file.action FROM $fetch => "<--", $store => "-->", $check => "<-->", ENDCASE => NIL]], [rope[file.remoteFile]], [rope[DFUtilities.DateToRope[[$explicit, file.date]]]], [rope[ SELECT file.dateFormat FROM $greaterThan => " > ", $notEqual => " ~= ", ENDCASE => NIL]] ]; }; ENDCASE; }; Rubout: ERROR = CODE; GetID: PROC [default: ROPE, echo: BOOL _ TRUE] RETURNS [id: ROPE] = { OPEN Ascii; firstTime: BOOL _ TRUE; c: CHAR; EraseAll: PROC = { IF echo THEN FOR i: INT DECREASING IN [0..id.Length[]) DO out.EraseChar[id.Fetch[i]]; ENDLOOP; id _ NIL; }; Done: PROC [c: CHAR] RETURNS [BOOL] = INLINE { IF firstTime THEN { SELECT c FROM ControlA, BS, ControlQ, ControlW, ControlX, '\n, ' => NULL; ENDCASE => EraseAll[]; firstTime _ FALSE; }; RETURN[c = ' OR c = '\n] }; id _ default; IF echo THEN out.PutRope[default]; c _ in.GetChar[ ! SimpleTerminal.InputTimeout => --RETURN--GO TO defaultReturn]; UNTIL Done[c] DO SELECT c FROM DEL => {out.PutRope[" XXX\N"]; ERROR Rubout}; ControlA, BS => { len: INT _ id.Length[]; IF len > 0 THEN { len _ len - 1; IF echo THEN out.EraseChar[id.Fetch[len]]; id _ id.Substr[len: len]; }; }; ControlW, ControlQ => { alpha: BOOL _ FALSE; FOR i: INT DECREASING IN [0..id.Length[]) DO ch: CHAR = id.Fetch[i]; SELECT TRUE FROM Ascii.Letter[ch], Ascii.Digit[ch] => alpha _ TRUE; alpha => {id _ id.Substr[len: i + 1]; EXIT}; ENDCASE; IF echo THEN out.EraseChar[ch]; REPEAT FINISHED => id _ NIL; ENDLOOP; }; ControlX => EraseAll[]; ENDCASE => {id _ id.Concat[Rope.FromChar[c]]; IF echo THEN out.PutChar[c]}; c _ in.GetChar[ ! SimpleTerminal.InputTimeout => RESUME]; ENDLOOP; EXITS defaultReturn => NULL; }; FileDesc: TYPE = RECORD [name: ROPE _ NIL, date: BasicTime.GMT _ BasicTime.nullGMT]; DFList: TYPE = REF DFListObject; DFListObject: TYPE = RECORD [head: LIST OF FileDesc _ NIL, tail: LIST OF FileDesc _ NIL]; systemID: ROPE = IO.PutFR["%g.%g.%g", [cardinal[SystemVersion.release.major]], [cardinal[SystemVersion.release.minor]], [cardinal[SystemVersion.release.patch]] ]; systemID2: ROPE = IO.PutFR["%g.%g", [cardinal[SystemVersion.release.major]], [cardinal[SystemVersion.release.minor]] ]; stamp: FileDesc _ []; stampName: ROPE _ Rope.Concat["InstallationStamp.", systemID]; longDialogue: BOOL _ Booting.switches[l]; development: BOOL _ TRUE; haveEssentials: BOOL _ FALSE; haveProfile: BOOL _ FALSE; essentials: FileDesc _ []; profile: FileDesc _ []; profileDFList: DFList = NEW[DFListObject _ []]; newProfileDFList: DFList = NEW[DFListObject _ []]; ParseInstallationStamp: PROC = { ForgetStamp[]; stamp _ TryFile[stampName].desc; IF stamp.date ~= BasicTime.nullGMT THEN { in: IO.STREAM = FS.StreamOpen[stamp.name ! FS.Error => GO TO noStamp]; GetFileDesc: PROC RETURNS [desc: FileDesc] = { desc.name _ StripVersion[in.GetTokenRope[IO.IDProc].token]; desc.date _ in.GetTime[]; }; DO ENABLE { IO.EndOfStream, IO.Error => GO TO parsingProblem; FS.Error => IF error.group = $user THEN GO TO parsingProblem ELSE REJECT; }; itemName: ROPE = in.GetTokenRope[IO.IDProc ! IO.EndOfStream => EXIT].token; SELECT TRUE FROM itemName.Equal["Essentials"] => IF essentials.name = NIL THEN essentials _ GetFileDesc[] ELSE GO TO parsingProblem; itemName.Equal["Profile"] => IF profile.name = NIL THEN profile _ GetFileDesc[] ELSE GO TO parsingProblem; itemName.Equal["UserDF"] => AddToDFList[profileDFList, GetFileDesc[]]; itemName.Equal["User"] => { userInProfile: ROPE = in.GetTokenRope[IO.IDProc].token; IF NOT Rope.Equal[user, userInProfile, FALSE] THEN { profile _ []; profileDFList^ _ []; }; EXIT; }; ENDCASE => GO TO parsingProblem; REPEAT parsingProblem => {in.Close[]; GO TO noStamp}; ENDLOOP; in.Close[]; }; EXITS noStamp => ForgetStamp[]; }; WriteStamp: PROC = { out: IO.STREAM = FS.StreamOpen[StripVersion[stampName], $create ! FS.Error => GO TO noStamp]; PutFileDesc: PROC [head: ROPE, desc: FileDesc] = { IO.PutF[out, "%g: %g %g\N", [rope[head]], [rope[desc.name]], [rope[DFUtilities.DateToRope[[$explicit, desc.date]]]] ]; }; IF essentials.name ~= NIL AND essentials.date ~= BasicTime.nullGMT THEN PutFileDesc["Essentials", essentials]; IF profile.name ~= NIL AND profile.date ~= BasicTime.nullGMT THEN PutFileDesc["Profile", profile]; FOR l: LIST OF FileDesc _ newProfileDFList.head, l.rest UNTIL l = NIL DO IF l.first.date ~= BasicTime.nullGMT THEN PutFileDesc["UserDF", l.first]; ENDLOOP; IO.PutF1[out, "User: %g\n", [rope[user]]]; out.Close[]; stamp _ []; EXITS noStamp => NULL; }; ForgetStamp: PROC = { essentials _ profile _ []; profileDFList^ _ []; }; FindBootEssentials: PROC = { IF Booting.switches[q] THEN {haveEssentials _ TRUE; RETURN}; IF longDialogue THEN haveEssentials _ Confirm["Shall I assume the local files essential for booting are current?", FALSE]; IF ~haveEssentials THEN { name: ROPE = "BootEssentials.df"; desc: FileDesc _ TryFile[name, topPath].desc; SELECT TRUE FROM desc.date ~= BasicTime.nullGMT => haveEssentials _ ~ development AND essentials.date = desc.date AND essentials.name.Equal[StripVersion[desc.name], FALSE] AND (~longDialogue OR ~Confirm[ desc.name.Concat[ " was brought over the last time; shall I do it again anyway?"], TRUE ]); ENDCASE => WHILE Confirm["Do you want to specify a DF file for booting essentials?"] DO fileName: ROPE = FS.ExpandName[name, topPath].fullFName; out.PutRope["DF file for booting essentials: "]; desc _ TryFile[GetID[fileName ! Rubout => LOOP]].desc; IF desc.date = BasicTime.nullGMT THEN out.PutRope["...not found\N"] ELSE {out.PutChar[Ascii.CR]; EXIT}; REPEAT FINISHED => { out.PutRope["The files essential for booting can't be found. I give up.\N"]; Die[]; }; ENDLOOP; essentials _ desc; }; }; FindUserProfile: PROC = { localDesc: FileDesc; remoteDesc: FileDesc; attachedTo: ROPE; { [fullFName: localDesc.name, attachedTo: attachedTo, created: localDesc.date] _ OpenInfo[name: "[]<>Server.profile" ! FS.Error => { IF error.code # $unknownFile THEN { OpenTerminal[]; IO.PutF1[out, "Note: Server.profile problem (%g).\n", [rope[error.explanation]] ]; }; GO TO notServer; }]; RETURN; EXITS notServer => {}; }; localDesc.name _ FS.ExpandName[name: localProfile, wDir: homeDir].fullFName; [fullFName: localDesc.name, attachedTo: attachedTo, created: localDesc.date] _ OpenInfo[name: localDesc.name ! FS.Error => { OpenTerminal[]; SELECT error.code FROM $unknownFile => IO.PutF1[out, "Note: no local profile found (%g).\n", [rope[localDesc.name]] ]; ENDCASE => IO.PutF1[out, "Note: local profile problem (%g).\n", [rope[error.explanation]] ]; CONTINUE; }]; remoteDesc.name _ FS.ExpandName[name: localProfile, wDir: userPath].fullFName; [fullFName: remoteDesc.name, created: remoteDesc.date] _ OpenInfo[name: remoteDesc.name ! FS.Error => { IF in = NIL AND localDesc.date # BasicTime.nullGMT THEN CONTINUE; OpenTerminal[]; SELECT error.code FROM $unknownFile => IO.PutF1[out, "Note: no remote profile found (%g).\n", [rope[remoteDesc.name]] ]; ENDCASE => IO.PutF1[out, "Note: remote profile problem (%g).\n", [rope[error.explanation]] ]; CONTINUE; }]; profile _ []; SELECT TRUE FROM localDesc.date = BasicTime.nullGMT OR (localDesc.date # remoteDesc.date AND remoteDesc.date # BasicTime.nullGMT) => { installIfTimeout: BOOL _ TRUE; IF localDesc.date#BasicTime.nullGMT AND remoteDesc.date#BasicTime.nullGMT THEN { OpenTerminal[]; IO.PutF[out, "Local profile is %g (%g) than remote version (%g)\n", [rope[IF BasicTime.Period[remoteDesc.date, localDesc.date] > 0 THEN "newer" ELSE "older"]], [time[localDesc.date]], [time[remoteDesc.date]] ]; }; WHILE Confirm["Do you wish to install a personal profile?", installIfTimeout] DO profileName: ROPE _ FS.ExpandName[localProfile, userPath].fullFName; remote: FileDesc _ []; out.PutRope[" Personal profile name: "]; remote.name _ GetID[profileName ! Rubout => LOOP]; remote.name _ FS.ExpandName[name: remote.name, wDir: userPath].fullFName; [fullFName: remote.name, created: remote.date] _ OpenInfo[name: remote.name ! FS.Error => { SELECT error.code FROM $unknownFile => IO.PutF1[out, " ... %g not found\n", [rope[remoteDesc.name]] ]; ENDCASE => IO.PutF1[out, " ... not available (%g).\n", [rope[error.explanation]] ]; installIfTimeout _ ~remote.name.Equal[profileName]; LOOP; }]; IO.PutChar[out, '\n]; profile _ remote; localDesc.name _ FS.Copy[ from: remote.name, to: Rope.Concat[homeDir, localProfile], keep: 2, attach: FALSE ! FS.Error => { IO.PutF1[out, " ... not copied (%g).\n", [rope[error.explanation]] ]; installIfTimeout _ FALSE; LOOP}]; localDesc.date _ OpenInfo[localDesc.name].created; EXIT; ENDLOOP; }; ENDCASE => { haveProfile _ TRUE; IF attachedTo ~= NIL THEN profile _ [attachedTo, localDesc.date]; }; }; TryForFonts: PROC = { GetFonts: PROC [name: ROPE, wDir: ROPE] ~ { key: ROPE ~ Rope.Cat["Installer.", name, "DF"]; defaultVal: ROPE ~ Rope.Cat["[Fonts]Top>", name, ".df"]; dfFile: ROPE ~ UserProfile.Token[key, defaultVal]; innerGetFonts: PROC = { IF TryFile[dfFile, NIL].desc.date # BasicTime.nullGMT THEN [] _ DFOperations.BringOver[dfFile: dfFile, interact: Interact, action: enter]; }; ProcessProps.PushPropList[List.PutAssoc[$WorkingDirectory, wDir, NIL], innerGetFonts]; }; IF FSPseudoServers.Lookup["Fonts"] = NIL THEN { psList: FSPseudoServers.PseudoServerList _ FSPseudoServers.PseudoServerFromRope[UserProfile.Token["Installer.FontsServer", "Fonts $ Cyan"]].new; IF psList # NIL THEN IF psList.first.read # NIL AND Rope.Equal[psList.first.server, "Fonts", FALSE] THEN FSPseudoServers.InsertPseudoServer[psList]; }; GetFonts["TiogaFonts", "///Fonts/Xerox/TiogaFonts"]; GetFonts["PressFonts", "///Fonts/Xerox/PressFonts"]; GetFonts["FontMetrics", "///Fonts/FontMetrics"]; }; AddToDFList: PROC [list: DFList, desc: FileDesc] = { descL: LIST OF FileDesc = CONS[desc, NIL]; IF list.head = NIL THEN list.head _ descL ELSE list.tail.rest _ descL; list.tail _ descL; }; installedUser: ROPE _ NIL; user: ROPE _ NIL; localProfile: ROPE _ NIL; userPath: ROPE _ NIL; topPath: ROPE _ NIL; homeDir: ROPE _ "///"; InitUserRelatedInfo: PROC = { remoteNames: DefaultRemoteNames.DefaultNames = DefaultRemoteNames.Get[]; installedUser _ UserCredentials.Get[].name; user _ installedUser.Substr[len: installedUser.SkipTo[skip: "."]]; localProfile _ user.Concat[".profile"]; userPath _ IO.PutFR["%g<%g>%g>", [rope[remoteNames.userHost]], [rope[user]], [rope[systemID2]] ]; topPath _ Rope.Concat[remoteNames.current, "Top>"]; }; OpenInfo: PROC [name: ROPE, wDir: ROPE _ NIL] RETURNS [fullFName: ROPE, attachedTo: ROPE, created: BasicTime.GMT] = { file: FS.OpenFile _ FS.Open[name: name, wDir: wDir]; { ENABLE UNWIND => FS.Close[file]; [fullFName, attachedTo] _ FS.GetName[file]; created _ FS.GetInfo[file].created; FS.Close[file]; }; }; OpenTerminal: PROC = { IF in # NIL THEN RETURN; [in, out] _ SimpleTerminal.TurnOn[]; out.PutChar[Ascii.CR]; }; CloseTerminal: PROC = { IF in = NIL THEN RETURN; SimpleTerminal.TurnOff[]; in _ out _ NIL; }; TryFile: PROC [shortName, prefix: ROPE _ NIL] RETURNS [desc: FileDesc _ [], attachedTo: ROPE _ NIL] = { [fullFName: desc.name, attachedTo: attachedTo, created: desc.date] _ OpenInfo[name: shortName, wDir: prefix ! FS.Error => CONTINUE]; }; StripVersion: PROC [old: ROPE] RETURNS [new: ROPE] = { cp: FS.ComponentPositions; [fullFName: new, cp: cp] _ FS.ExpandName[old ! FS.Error => GO TO none]; new _ new.Substr[len: cp.ext.start+cp.ext.length]; EXITS none => {}; }; CheckAutoConfirm: PROC [df: ROPE] = { IF longDialogue AND autoConfirm THEN { msg: ROPE = Rope.Cat["Confirm retrieval of each file from ", df, " individually?"]; autoConfirm _ ~Confirm[msg, FALSE]; }; }; Die: PROC = {DO ENDLOOP}; NewUser: Booting.RollbackProc = { DoRealWork[TRUE]; }; NoteCredentialsChange: UserCredentials.CredentialsChangeProc = { IF NOT Idle.IsIdle[] THEN DoRealWork[TRUE]; }; IdleOver: Idle.IdleHandler = { IF reason = becomingBusy THEN DoRealWork[TRUE]; }; working: BOOL _ FALSE; DoRealWork: PROC [rolling: BOOL _ FALSE] = { IF working THEN RETURN; working _ TRUE; haveEssentials _ haveProfile _ FALSE; IF longDialogue AND ~Confirm["Long installation dialogue [confirm] "] THEN { out.PutRope["(L-switch now cleared.)\N"]; longDialogue _ Booting.switches[l] _ FALSE; }; IF ~longDialogue THEN SimpleTerminal.SetInputTimeout[Process.SecondsToTicks[30]]; InitUserRelatedInfo[]; ParseInstallationStamp[]; IF NOT rolling THEN FindBootEssentials[]; FindUserProfile[]; IF NOT haveEssentials AND NOT rolling THEN { CheckAutoConfirm[essentials.name]; [] _ DFOperations.BringOver[dfFile: essentials.name, interact: Interact, action: fetch]; }; WriteStamp[]; SELECT TRUE FROM rolling => UserProfile.ProfileChanged[rollBack]; Booting.switches[q] => UserProfile.ProfileChanged[firstTime]; ENDCASE => { haveFonts: BOOL _ FALSE; UserProfile.ProfileChanged[firstTime]; IF longDialogue THEN haveFonts _ Confirm["Shall I assume the fonts are current?", FALSE]; IF NOT haveFonts THEN TryForFonts[]; }; SimpleTerminal.SetInputTimeout[0]; CloseTerminal[]; working _ FALSE; }; YNQA: TYPE = {yes, no, quit, all}; ynqa: REF DFOperations.Choices = NEW[DFOperations.Choices[YNQA.LAST.ORD.SUCC - YNQA.FIRST.ORD]]; yesNo: REF DFOperations.Choices = NEW[DFOperations.Choices[BOOL.LAST.ORD.SUCC - BOOL.FIRST.ORD]]; yesNo[BOOL.TRUE.ORD] _ "Yes"; yesNo[BOOL.FALSE.ORD] _ "No"; ynqa[YNQA.yes.ORD] _ "Yes"; ynqa[YNQA.no.ORD] _ "No"; ynqa[YNQA.quit.ORD] _ "Quit"; ynqa[YNQA.all.ORD] _ "All"; IF Booting.switches # [] THEN { OpenTerminal[]; IO.PutRope[out, "\NBoot switches:"]; FOR sw: GermSwap.Switch IN GermSwap.Switch DO IF Booting.switches[sw] THEN { out.PutChar[Ascii.SP]; out.PutChar[VAL[(IF sw <= nine THEN '0 ELSE 'A-10)+sw.ORD]]; }; ENDLOOP; out.PutChar[Ascii.CR]; }; DoRealWork[FALSE ! FS.Error => { OpenTerminal[]; IO.PutF1[out, "\NFatal FS Error: %g\N", [rope[error.explanation]]]; Die[]; } ]; Booting.RegisterProcs[r: NewUser]; [] _ Idle.RegisterIdleHandler[IdleOver]; UserCredentials.RegisterForChange[proc: NoteCredentialsChange, clientData: NIL] END. xInstallerImpl.mesa Copyright c 1984, 1985 by Xerox Corporation. All rights reserved. Willie-Sue, July 30, 1984 3:56:10 pm PDT Russ Atkinson (RRA) August 20, 1985 11:30:21 am PDT Doug Wyatt, May 23, 1985 5:01:01 pm PDT User interaction stuff text to be backed up is of the form ..., the and following are to be removed. Installation Stamp The format of the installation stamp file is as follows: Essentials: name and date of (remote) boot essentials file used ?(Profile: name and date of (remote) user profile used ) (UserDF: name and date of (remote) user-specified DF and date ) ... Initialized by InitUserRelatedInfo. If TRUE, forces retrieval of BootEssentials every time we are fully booted. RRA: For now, always force it to be TRUE until we can get a more reliable way of determining if the release is "frozen". RRA: the profile is both read from and written to the installation stamp, but our current algorithm for determining the validity of the loacl profile does NOT use this information. This makes it primarily useful for debugging. This item is the LAST in the installation stamp The profile and profileDFList are both bogus, but the essentials may be OK. Note: If the stamp was originally missing or invalid and the user explicitly prohibited retrieval of boot essentials, 'essentials' will be garbage. In this case, we don't write a new "Essentials" entry, and the user will be hassled the next time he boots. We depend on the User item being written last! Upon return, if 'haveEssentials' is TRUE, the contents of 'essentials' are unpredictable. If 'haveEssentials' is FALSE, however, 'essentials' describes an extant file to which BringOver is to be applied. Upon return, if 'haveProfile' is TRUE, no profile change notification is required. If 'haveProfile' is FALSE, however, any necessary file retrieval has occurred and, if the fields of 'profile' do not have their default values, they describe a remote file to be included in the stamp. Profile change notification should occur after the BringOver of the boot essentials is completed, so that the system default profile can be mentioned therein and noticed at the proper time. First, try for []<>Server.profile, since it overrides any user profile. RRA: No reason to inform the user that there is a remote problem if the local profile exists, we will just assume that the local version is OK. There is no personal profile on the local disk OR it has a different date from the default remote profile (but NOT if there is a local profile and no remote profile). The user gets the opportunity to specify one; if he chooses not to, the system default will be used (we assume the files essential for booting include a default profile). Loops until remote file is located or user decides against using one. Copy the remote file to the local profile copy. There is a local profile on the disk, and it matches the remote profile. So we trust the local profile. This is a reasonable Fonts pseudo-server specification Miscellaneous Strictly speaking we initialize more here than just the user related info, but it is a good place to initialize various flags and paths. This procedure is similar to FS.FileInfo, except that it also makes certain that the file is on the local disk. Any errors raised by FS.Open are the respobsibility of the caller. Main body [clientData: REF ANY] If there is a credentials change that is NOT part of coming back from Idle, then we do the same work as for coming out of Idle (or Rollback). When we come back from Idle and the user changes, then we get a user profile notification of rollBack even though we do not get a rollback notification from Booting (sigh). Therefore, we also register to do the real work on this event. However, since we can also change the user profile when doing the real work, we have to avoid recursion, which we do by calling with `fromProfile' = TRUE. Someday someone should get ambitious and fix all of this crap. The profile may have changed due to the rollback. Even if it hasn't, we notify. This is the first time through, so it's time to get ourselves a user profile Try for the initial set of fonts Ê·˜codešœ™Kšœ Ïmœ7™BK™(K™3K™'—K˜šÏk ˜ Kš œžœžœ)žœžœžœ˜UKšœ žœžœ˜'Kšœžœ)˜6Kšœžœ˜-Kšœ žœ¡˜³Kšœ žœ˜Kšžœžœd˜lKšœžœF˜[Kšœ žœ ˜Kšœžœ,˜6Kšžœžœvžœ˜†Kšœžœ ˜Kšœžœ˜Kšœ žœ˜"Kšœžœ/žœ˜OKšœžœ2˜FKšœžœ ˜Kšœ žœ˜)Kšœžœ1˜FKšœ žœ˜*—K˜šÐbl œžœž˜KšžœKžœžœj˜ÙKšœž˜K˜Kšžœžœžœ˜K˜Kšœ žœžœžœ˜—K˜Kšœ™™š Ïn œžœžœ!žœ žœ˜Qšž˜Kšœ žœ!˜.Kšœžœžœ˜Kšœ žœžœ˜š  œžœ˜Kš œžœžœ žœ žœ˜-š žœžœž œžœž˜+Kšœ˜Kšžœ˜—Kšœžœ˜ Kšœ˜Kšœ žœ˜K˜—Kšžœžœžœžœ˜7Kšœ*žœ˜.Kšœ˜šž˜Kšœžœ˜Kšœžœ˜ KšœBžœžœ˜Qšžœž˜Kšœžœžœžœ ˜6Kš œžœžœžœžœžœ˜0šœžœ˜Kšžœ žœ˜ šž˜šžœžœ˜Kšœ)˜)Kšœ&˜&K˜———KšœA˜Ašœ˜Kšœ#˜#šžœžœžœž˜&Kšžœžœ˜!Kšœ˜Kšžœ˜—Kšœžœ˜šžœžœž˜šžœžœžœž˜+šžœžœžœ˜"Kšœ˜Kšœžœ˜K˜—Kšžœ˜——Kšžœžœ ˜K˜—šžœ˜ Kšœ/˜/Kšžœ žœ˜!Kšœ&˜&šžœžœžœž˜&šžœ=žœžœ˜LKšžœ&žœžœ˜Ošžœž˜Kšœ(˜(Kšœ˜Kšžœ˜—K˜—Kšžœ˜—šžœž˜šœ ˜ Kšœ,˜,Kšœ ˜ Kšœ˜—šœ ˜ Kšœ>˜>Kšžœžœ˜ Kšœ˜—KšœC˜CKšžœ˜—K˜——šž˜Kšœ žœ˜—Kšžœ˜—šž˜Kšœžœ˜ —Kšžœ˜—Kšœžœ˜K˜—K˜š œžœ žœ žœžœžœžœ˜Fšœžœ"žœ#˜NKšœ˜Kšœ˜Kšœžœ˜Kšœž˜K˜—K˜Kšžœžœ˜K˜—K˜Kšœ žœžœ˜K˜Kšœžœ˜K˜šœ+˜+K˜šžœ žœž˜šœžœ"˜+Kšœžœžœ˜Kšžœžœžœžœ˜7šžœ ž˜Kšœžœ˜Kšœ$˜$Kšœ ˜ Kšœ žœ˜Kšžœ˜—Kšœ˜Kšœžœ˜šžœžœ˜Kšžœ%žœžœ˜3K˜K˜K˜—K˜—šœžœ$˜-šžœ ž˜šœ ˜ Kšœžœ˜Kšžœžœžœžœ˜7K˜K˜K˜—šœ˜Kšžœžœžœžœ˜7K˜!K˜Kšœžœ˜K˜—šœ ˜ K˜K˜K˜Kšœ ˜ Kšœ˜—Kšžœ˜—Kšžœžœžœžœ+˜IKšœžœ˜K˜—šœžœ"˜(šžœ žœž˜!Kšžœ žœ0˜D——šœžœ!˜(šžœ žœžœ˜$šœžœ"žœ#˜NKšœ˜Kšœ˜Kšœžœ˜Kšœ žœ žœžœžœžœžœž˜9K˜—Kšœžœžœ˜!šžœž˜Kšœžœ žœžœ˜CKšœžœ žœžœ˜C˜ Kšœžœ˜ K˜+K˜—šœ ˜ Kšœžœ˜Kšžœ žœžœ˜:Kšœ˜—Kšžœ˜—K˜——šœžœ ˜)šžœ žœ˜Kšžœžœžœžœ˜7šžœ˜!Kšœ˜šœžœ ž˜Kšœ4žœžœ˜E—Kšœ˜Kšœ7˜7šœ˜šžœž˜Kšœ˜Kšœ˜Kšžœžœ˜——Kšœ˜—K˜——Kšžœ˜—K˜—K˜Kšœžœžœ˜K˜š œžœ žœžœžœžœžœ˜EKšžœ˜ Kšœ žœžœ˜Kšœžœ˜š œžœ˜šžœž˜ Kš žœžœž œžœžœžœ˜Q—Kšœžœ˜ K˜—š  œžœžœžœžœžœ˜.šžœ žœ˜šžœž˜ Kšœ žœ+žœ˜K˜Kšœžœ˜)šœ žœžœ˜Kšœp™pKšœy™y—K˜Kšœžœžœ˜Kšœ žœžœ˜K˜Kšœ˜šœ˜Kšœã™ã—Kšœžœ˜/Kšœžœ˜2K˜š œžœ˜ Kšœ˜Kšœ ˜ šžœ!žœ˜)Kš œžœžœžœžœ žœžœ ˜Fš  œžœžœ˜.Kšœ)žœ˜;Kšœ˜K˜—šž˜šžœ˜Kšžœžœ žœžœ˜1Kšžœ žœžœžœžœžœžœ˜IK˜—Kš œ žœžœ žœžœ˜Kšžœžœž˜šœ˜Kšžœžœžœ˜8Kšžœžœžœ˜—šœ˜Kšžœžœžœ˜2Kšžœžœžœ˜—KšœF˜Fšœ˜Kšœ/™/Kšœžœžœ˜7šžœžœ!žœžœ˜4KšœK™KKšœ ˜ Kšœ˜Kšœ˜—Kšžœ˜Kšœ˜—Kšžœžœžœ˜ —šž˜Kšœžœžœ ˜.—Kšžœ˜—K˜ K˜—šž˜Kšœ˜—Kšœ˜—K˜š  œžœ˜šœžœžœžœ,˜?Kšœžœ žœžœ ˜—š  œžœžœ˜2šžœ˜Kšœ ˜ Kšœ˜Kšœ6˜6Kšœ˜—K˜—Kšœ™šžœžœžœ&ž˜GKšœ&˜&—šžœžœžœ#ž˜AKšœ ˜ —š žœžœžœ*žœžœž˜HKšžœ#žœ ˜IKšžœ˜—šžœ(˜*Kšœ.™.—K˜ K˜ šž˜Kšœ žœ˜—K˜—K˜š  œžœ˜Kšœ˜Kšœ˜K˜—K˜š œžœ˜Kšœ$žœJžœU™ÌKšžœžœžœžœ˜<šžœž˜šœ˜KšœMžœ˜T——šžœžœ˜Kšœžœ˜!Kšœ-˜-šžœžœž˜šœ!˜!šœ˜Kšœž˜Kšœž˜Kšœ/žœž˜9šœžœ ˜šœ˜Kšœ@˜@—Kšž˜K˜———šžœ˜ šžœEž˜LKšœ žœžœ%˜8K˜0Kšœ*žœ˜6šžœ˜ Kšžœ˜"Kšžœžœžœ˜#—šž˜šžœ˜ K˜MK˜K˜——Kšžœ˜———Kšœ˜K˜—K˜K˜—š œžœ˜Kšœ!žœCžœï™ÜKšœ˜Kšœ˜Kšœ žœ˜˜KšœG™GšœN˜Nšœ&žœ ˜3šžœžœ˜#Kšœ˜KšžœP˜RK˜—Kšžœžœ ˜K˜——Kšžœ˜Kšžœ˜K˜—Kšœžœ9˜LšœN˜Nšœ žœ ˜-Kšœ˜šžœ ž˜šœ˜KšžœM˜O—šžœ˜ KšžœO˜Q——Kšžœ˜ Kšœ˜——Kšœžœ:˜Nšœ8˜8šœ!žœ ˜.š žœžœžœ$žœžœ˜AKšžœ‰žœ™—Kšœ˜šžœ ž˜šœ˜KšžœO˜Q—šžœ˜ KšžœP˜R——Kšžœ˜ Kšœ˜——K˜K˜ šžœžœž˜šœ#žœ#žœ*˜uKšœ/žœ>žœà™ÒKšœžœžœ˜šžœ"žœ#žœ˜PKšœ˜šžœA˜Cšœžœ6˜>Kšžœ žœ ˜—Kšœ/˜/Kšœ˜—K˜—K˜šžœIž˜PKšœE™EKšœ žœžœ.˜DK˜K˜)Kšœ,žœ˜2Kšœžœ9˜Išœ0˜0šœžœ ˜*šžœ ž˜šœ˜Kšžœ=˜?—šžœ˜ KšžœF˜H——Kšœ3˜3Kšžœ˜Kšœ˜——Kšœ/™/Kšžœ˜Kšœ˜šœžœ˜Kšœ˜Kšœ'˜'Kšœ˜Kšœž˜ šœžœ ˜KšžœC˜EKšœžœ˜Kšžœ˜——Kšœ2˜2Kšžœ˜Kšžœ˜—K˜—šžœ˜ K™hKšœžœ˜Kšžœžœžœ(˜AK˜——K˜K˜—š  œžœ˜š œžœžœžœ˜+Kšœžœ&˜/Kšœ žœ4˜DKšœžœ&˜2šœžœ˜šžœžœ ž˜:KšœO˜O—K˜—KšœAžœ˜VK˜—šžœ#žœžœ˜/Kšœ˜šžœ žœž˜š žœžœžœ*žœž˜SKšœ6™6Kšœ+˜+——K˜—Kšœ4˜4Kšœ4˜4Kšœ0˜0K˜K˜—š  œžœ#˜4Kš œžœžœ žœžœ˜*Kšžœ žœžœžœ˜FKšœ˜K˜—K˜—K™ ˜Kšœž œ˜Kšœž œ˜Kšœž œ˜Kšœ žœžœ˜Kšœ žœžœ˜Kšœ žœ ˜K˜š œžœ˜Kšœˆ™ˆKšœH˜HKšœ+˜+KšœB˜BKšœ'˜'šœ žœ˜ Kšœ@˜@—Kšœ3˜3K˜K˜—š œžœžœžœžœžœ žœžœžœ˜uKšœžœgžœ+™³Kšœžœ žœ˜4˜Kšžœžœžœ ˜ Kšœžœ˜+Kšœ žœ˜#Kšžœ ˜Kšœ˜—K˜—K˜š  œžœ˜Kšžœžœžœžœ˜K˜$Kšœžœ˜K˜K˜—š  œžœ˜Kšžœžœžœžœ˜K˜Kšœ žœ˜K˜K˜—š œžœžœžœžœ#žœžœ˜gšœD˜DKšœ)žœ žœ˜?—K˜—K˜š   œžœžœžœžœ˜6Kšœžœ˜Kš œžœžœ žœžœ˜GK˜2Kšžœ ˜K˜—K˜š œžœžœ˜%šžœžœ žœ˜&KšœžœJ˜SKšœžœ˜#K˜—K˜—K˜Kš œžœžœžœ˜—K™Kšœ ™ ˜šœ!˜!Kšœ žœ˜K˜K˜—•StartOfExpansion -- [clientData: REF ANY]šœ@˜@KšÐck™Kšœ™Kšžœžœžœ žœ˜+K˜K˜—šœ˜KšœƒžœA™ÈKšžœžœ žœ˜/K˜K˜—šœ žœžœ˜K˜—š  œžœ žœžœ˜,Kšžœ žœžœ˜Kšœ žœ˜Kšœžœ˜%šžœžœ3žœ˜LKšœ)˜)Kšœ%žœ˜+K˜—Kšžœžœ<˜QK˜Kšœ˜Kšžœžœ žœ˜)K˜š žœžœžœžœ žœ˜,Kšœ"˜"KšœX˜XK˜—K˜ šžœžœž˜˜ K™PKšœ%˜%—Kšœ=˜=šžœ˜ Kšœ žœžœ˜KšœL™LKšœ&˜&Kšœ!™!šžœž˜Kšœ=žœ˜D—Kšžœžœ žœ˜$K˜——Kšœ"˜"K˜Kšœ žœ˜K˜——K˜Kšžœžœ˜"Kšœžœžœžœžœžœžœžœžœžœ˜`Kšœžœžœžœžœžœžœžœžœžœ˜aK˜Kšœžœžœžœ ˜Kšœžœžœžœ ˜Kšœžœžœ ˜Kšœžœžœ ˜Kšœžœžœ ˜Kšœžœžœ ˜K˜šžœžœ˜K˜Kšžœ"˜$šžœžœž˜-šžœžœ˜Kšœžœ˜Kš œ žœžœ žœžœ žœ˜