InstallerImpl.mesa
Copyright © 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
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.STREAMNIL;
User interaction stuff
GetChoice: PROC [c: REF DFOperations.ChoiceInteraction] RETURNS [choice: NAT] = {
DO
default: ROPE = c.choices[choice ← c.default];
ans: ROPENIL;
firstChar: BOOLTRUE;
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: BOOLTRUE] RETURNS [BOOL] = {
c: REF DFOperations.ChoiceInteraction = NEW[DFOperations.ChoiceInteraction ← [
message: message,
choices: yesNo,
explanations: NIL,
default: default.ORD
]];
OpenTerminal[];
RETURN[VAL[GetChoice[c]]]
};
autoConfirm: BOOLTRUE;
depth: INT ← -1;
Interact: DFOperations.InteractionProc = {
OpenTerminal[];
WITH interaction SELECT FROM
info: REF DFOperations.InfoInteraction => {
prompt: BOOLTRUE;
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: BOOLTRUE] RETURNS [id: ROPE] = {
OPEN Ascii;
firstTime: BOOLTRUE;
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 => {
text to be backed up is of the form ...<non-alpha><alpha><non-alpha>, the <alpha> and following <non-alpha> are to be removed.
alpha: BOOLFALSE;
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;
};
Installation Stamp
The format of the installation stamp file is as follows:
Essentials: name and date of (remote) boot essentials file used <CR>
?(Profile: name and date of (remote) user profile used <CR>)
(UserDF: name and date of (remote) user-specified DF and date <CR>) ...
FileDesc: TYPE = RECORD [name: ROPENIL, 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: BOOLTRUE;
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".
haveEssentials: BOOLFALSE;
haveProfile: BOOLFALSE;
essentials: FileDesc ← [];
profile: FileDesc ← [];
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.
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"] => {
This item is the LAST in the installation stamp
userInProfile: ROPE = in.GetTokenRope[IO.IDProc].token;
IF NOT Rope.Equal[user, userInProfile, FALSE] THEN {
The profile and profileDFList are both bogus, but the essentials may be OK.
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]]]]
];
};
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.
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]]];
We depend on the User item being written last!
out.Close[];
stamp ← [];
EXITS
noStamp => NULL;
};
ForgetStamp: PROC = {
essentials ← profile ← [];
profileDFList^ ← [];
};
FindBootEssentials: PROC = {
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.
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 = {
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.
localDesc: FileDesc;
remoteDesc: FileDesc;
attachedTo: ROPE;
{
First, try for []<>Server.profile, since it overrides any user profile.
[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;
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.
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) => {
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).
installIfTimeout: BOOLTRUE;
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
Loops until remote file is located or user decides against using one.
profileName: ROPEFS.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;
}];
Copy the remote file to the local profile copy.
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 => {
There is a local profile on the disk, and it matches the remote profile. So we trust the local profile.
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]<CedarFonts>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
This is a reasonable Fonts pseudo-server specification
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;
};
Miscellaneous
installedUser: ROPE ← NIL;
user: ROPE ← NIL;
localProfile: ROPE ← NIL;
userPath: ROPENIL;
topPath: ROPENIL;
homeDir: ROPE ← "///";
InitUserRelatedInfo: PROC = {
Strictly speaking we initialize more here than just the user related info, but it is a good place to initialize various flags and paths.
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: ROPENIL] RETURNS [fullFName: ROPE, attachedTo: ROPE, created: BasicTime.GMT] = {
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.
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: ROPENIL] RETURNS [desc: FileDesc ← [], attachedTo: ROPENIL] = {
[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};
Main body
NewUser: Booting.RollbackProc = {
DoRealWork[TRUE];
};
NoteCredentialsChange: UserCredentials.CredentialsChangeProc = {
[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).
IF NOT Idle.IsIdle[] THEN DoRealWork[TRUE];
};
IdleOver: Idle.IdleHandler = {
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.
IF reason = becomingBusy THEN DoRealWork[TRUE];
};
working: BOOLFALSE;
DoRealWork: PROC [rolling: BOOLFALSE] = {
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 =>
The profile may have changed due to the rollback. Even if it hasn't, we notify.
UserProfile.ProfileChanged[rollBack];
Booting.switches[q] => UserProfile.ProfileChanged[firstTime];
ENDCASE => {
haveFonts: BOOLFALSE;
This is the first time through, so it's time to get ourselves a user profile
UserProfile.ProfileChanged[firstTime];
Try for the initial set of fonts
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.