CedarInitMain.mesa
last edited by Levin on April 19, 1983 11:07 am
last edited by McGregor on November 17, 1982 4:26 pm
last edited by Schmidt on January 31, 1983 6:20 pm
last edited by Paul Rovner on April 22, 1983 9:02 am
last edited by Russ Atkinson on June 8, 1983 12:13 pm
last edited by Doug Wyatt on September 15, 1983 11:00 am
DIRECTORY
Ascii USING [ControlA, BS, ControlQ, ControlW, ControlX, CR, DEL, ESC, FF, SP],
BodyDefs USING [maxRNameLength],
BringOverCall USING [CedarBringOver],
CedarInitOps USING [Seconds],
CedarInitPrivate USING [DoLoading, ErrorCode, FatalError, ValidateMicrocode],
CedarInitSequence USING [StartCedarCore, StartCedarUserInterface, StartCedarTools],
CedarSnapshot USING [RollBack],
CedarVersion USING [
bootFileDate, machineType, MachineType, major, minor, patch, uCodeCedar, uCodeDate,
uCodeVersion, uCodeFloatingPoint],
ConvertUnsafe USING[ToRope],
DateAndTimeUnsafe USING [Notes, Parse],
Directory USING [Error, GetProps, Lookup],
File USING [Capability, GetSize],
Format USING [Char, Date, Decimal, LongString, StringProc],
Heap USING [systemMDSZone, systemZone],
Inline USING [BITAND, LowHalf],
IO USING[CreateProcsStream, CreateRefStreamProcs, GetChar,
 Handle, PutF, PutFR, PutRope, Signal, string],
LongString USING [AppendString],
PilotClient USING [],
PilotSwitches USING [switches --.d, .l--],
Process USING [Pause, SecondsToTicks, Ticks],
ProcessorFace USING [PowerOff],
Rope USING [Equal, Lower, ROPE, Text],
RopeInline USING[InlineFlatten],
Runtime USING [GetBuildTime, IsBound],
Space USING [Create, Delete, Handle, Map, mds, Pointer],
SpecialTerminal USING [
DisableCursorTracking, DisableTypescriptFile, EnableCursorTracking,
EnableTypescriptFile, GetProc, InputTimeout, PutProc, SetInputTimeout,
TerminalOn, tty, TurnOff, TurnOffInternal, TurnOn, TurnOnInternal],
Storage USING [Free],
STP USING [
Close, CompletionProcType, ConfirmProcType, Create, CredentialsErrors, Destroy,
Enumerate, Error, FileErrors, FileInfo, GetFileInfo, Handle, Login, NoteFileProcType,
Open, Retrieve],
String USING [
AppendChar, AppendString, AppendSubString, EqualSubStrings, StringBoundsFault,
SubStringDescriptor],
System USING [
GetGreenwichMeanTime, GreenwichMeanTime, gmtEpoch, SecondsSinceEpoch],
TemporaryBooting USING [BootFromVolume, defaultSwitches, Switch],
TerminalMultiplex USING [
InputController, PermitDebuggerSwaps, PreventDebuggerSwaps,
RegisterInputController],
TTY USING [
CharsAvailable, GetChar, GetEditedString, GetID, Handle, LineOverflow,
LongSubStringDescriptor, PutChar, PutCR, PutDate, PutDecimal, PutLine,
PutLongString, PutString, PutLongSubString, PutSubString, SetEcho,
Rubout, UserAbort],
UserCredentials USING [
ChangeCredentialsState, GetCredentialsState, GetUserCredentials, Login,
SetUserCredentials, State],
UserCredentialsUnsafe USING [GetCredentialsState, GetUserCredentials, State],
UserTerminal USING [
Coordinate, cursor, CursorArray, GetCursorPattern, screenHeight, screenWidth,
SetBackground, SetCursorPattern, SetState],
Volume USING [GetType, ID, systemID];
CedarInitMain: MONITOR
IMPORTS
BringOverCall, CedarInitPrivate, CedarInitSequence, CedarSnapshot, CedarVersion,
ConvertUnsafe, DateAndTimeUnsafe, Directory, File, Format, Heap, Inline, IO, LongString,
PilotSwitches, Process, ProcessorFace, Rope, RopeInline, Runtime, Space, SpecialTerminal,
Storage, STP, String, System, TemporaryBooting, TerminalMultiplex, TTY, UserCredentials,
UserCredentialsUnsafe, UserTerminal, Volume
EXPORTS CedarInitOps, CedarVersion, PilotClient
SHARES SpecialTerminal =
BEGIN
-- Global Variables (not exported) --
basicCedar: BOOLEAN = ~Runtime.IsBound[CedarInitSequence.StartCedarCore];
initTTY: TTY.Handle; -- copy of SpecialTerminal.tty, for convenience
-- Exports to CedarVersion --
major: PUBLIC CARDINAL ← 4;
minor: PUBLIC CARDINAL ← 5;
patch: PUBLIC CARDINAL ← 0;
bootFileDate: PUBLIC System.GreenwichMeanTime ← Runtime.GetBuildTime[];
-- Exports to CedarInitOps --
longDialogue: PUBLIC BOOLEAN ← PilotSwitches.switches.l = down;
salvageLSD: PUBLIC BOOLFALSE; -- Eventually, CIFS should ask using the initial screen.
Install: PUBLIC PROC RETURNS [worked: BOOLEAN] = {RETURN[DoInstallation[booting: FALSE]]};
EnsureUsableMicrocode: PUBLIC ENTRY PROC = {
ucodeError: LONG STRING ← CedarInitPrivate.ValidateMicrocode[];
IF ucodeError = NIL THEN RETURN;
[] ← SpecialTerminal.TurnOn[];
ReportUCodeError[ucodeError];
SpecialTerminal.TurnOff[];
};
sleeping: BOOLEANFALSE;
napOver: CONDITION ← [timeout: 0];
Sleep: PUBLIC PROC [
cursor: LONG POINTER TO UserTerminal.CursorArray ← NIL,
powerOff: CedarInitOps.Seconds ← 0] = {
NapNeeded: ENTRY PROC RETURNS [needed: BOOL] = INLINE {
IF (needed ← ~sleeping) THEN sleeping ← TRUE
ELSE WHILE sleeping DO WAIT napOver ENDLOOP;
};
WakeUp: ENTRY PROC = {sleeping ← FALSE; BROADCAST napOver};
DoLogin: PROC RETURNS [wake: BOOLTRUE] = {
state: UserCredentials.State = UserCredentials.GetCredentialsState[];
name, password: Rope.ROPE;
[name, password] ← UserCredentials.GetUserCredentials[];
PrintGreeting[];
SpecialTerminal.SetInputTimeout[Process.SecondsToTicks[60]];
UserCredentials.Login[options: [confirmCredentialsOverwrite: TRUE, alwaysPrompt: TRUE]
! SpecialTerminal.InputTimeout => {wake ← FALSE; CONTINUE}];
IF wake THEN {
IF state = nameHint AND --HACK-- (powerOff ~= CedarInitOps.Seconds.LAST) AND
~Rope.Equal[UserCredentials.GetUserCredentials[].name, name, FALSE] THEN {
The user name isn't what it was before we went to sleep. To ensure the new user doesn't inadvertently access anything he shouldn't, we rollback or boot as appropriate, but first give him a chance to say it was all a mistake.
IF Confirm["You weren't previously logged in. To log you in, I will have to rollback.\NIs that what you want?"L ! SpecialTerminal.InputTimeout => CONTINUE] THEN {
CedarSnapshot.RollBack[Volume.systemID];
IF Confirm["Rollback failed. Shall I try to boot the system volume instead?"L] THEN
TemporaryBooting.BootFromVolume[Volume.systemID];
};
We end up here if the name supplied doesn't match the previously logged-in user, but the new user changes his mind and decides not to rollback. He can do so either by answering the above question negatively or by letting it time out. In either case, we restore previous user's credentials and go back to sleep. We must call ChangeCredentialsState because the Login call was successful, and since the credentials state is nameHint, Login rewrote the disk with the new user's credentials. However, since that user has changed his mind, we need to explicitly restore the old ones.
UserCredentials.SetUserCredentials[name, password];
[] ← UserCredentials.ChangeCredentialsState[state];
wake ← FALSE;
};
}
ELSE
Login has zapped the credentials, so we must restore them to their previous state. Since Login was aborted by the input timeout, the name hint on disk hasn't changed, so we need not call ChangeCredentialsState.
UserCredentials.SetUserCredentials[name, password];
SpecialTerminal.SetInputTimeout[0];
};
IF ~NapNeeded[] THEN RETURN;
TerminalMultiplex.PreventDebuggerSwaps[];
SleepInternal[DoLogin, cursor, powerOff];
TerminalMultiplex.PermitDebuggerSwaps[];
WakeUp[];
};
-- Sleep stuff --
SleepInternal: PROC [
actionProc: PROC RETURNS [wake: BOOL],
cursor: LONG POINTER TO UserTerminal.CursorArray ← NIL, powerOff: CedarInitOps.Seconds ← 0] = {
oldCursor: UserTerminal.CursorArray;
typeKey: UserTerminal.CursorArray ← [
002000B, 074000B, 140000B, 012767B, 012525B, 053566B, 111113B, 163100B,
000000B, 000000B, 154000B, 053520B, 062520B, 053360B, 155440B, 000140B];
ticksPerSecond: Process.Ticks = Process.SecondsToTicks[1];
The following ugliness arranges to get the special terminal turned on but without actually painting any characters. (However, the window may appear briefly, an artifact which should be cleaned up someday.) This has two purposes. First, it carefully tucks the primary bitmap out of harms' way. Second, it allows us to intercept the keyboard input without messing up any normal Cedar programs. Note that, if a running program calls UserTerminal to alter the cursor position or pattern, it will be "fixed" by the next iteration of the main loop below.
DisableGreeting[];
[] ← SpecialTerminal.TurnOn[];
EnableGreeting[];
oldCursor ← UserTerminal.GetCursorPattern[];
DO -- loops only if actionProc returns FALSE
fellAsleep: LONG CARDINAL = System.SecondsSinceEpoch[System.GetGreenwichMeanTime[]];
Random number stuff
nRandoms: CARDINAL = 20;
RandIndex: TYPE = [0..nRandoms);
randTable: ARRAY RandIndex OF CARDINAL ← [
30200, 27432, 62096, 39855, 17884, 58726, 55595, 20904, 28164, 27447,
34709, 35231, 33770, 31508, 40689, 1411, 20373, 3422, 62938, 40035];
randIndex: RandIndex ← 16;
Random: PROC RETURNS [r: CARDINAL] = {
This algorithm is stolen from DMT.
i: RandIndex;
randIndex ← IF randIndex = LAST[RandIndex] THEN FIRST[RandIndex] ELSE SUCC[randIndex];
i ← (randIndex + 3) MOD nRandoms;
r ← randTable[i] ← randTable[randIndex] + randTable[i];
};
[] ← UserTerminal.SetState[off];
[] ← UserTerminal.SetBackground[black];
IF cursor = NIL THEN cursor ← @typeKey;
UserTerminal.SetCursorPattern[cursor^];
SpecialTerminal.DisableCursorTracking[];
DO
xy: UserTerminal.Coordinate ← UserTerminal.cursor^;
GetDelta: PROC RETURNS [INTEGER] = INLINE {
r: CARDINAL = Random[];
RETURN[
SELECT TRUE FROM
Inline.BITAND[r, 100000B] ~= 0 => 0,
Inline.BITAND[r, 40000B] ~= 0 => 16,
ENDCASE => -16]};
SELECT (xy.x ← xy.x + GetDelta[]) FROM
< 0 => xy.x ← UserTerminal.screenWidth - 16;
>= UserTerminal.screenWidth - 16 => xy.x ← 0;
ENDCASE;
SELECT (xy.y ← xy.y + GetDelta[]) FROM
< 0 => xy.y ← UserTerminal.screenHeight - 16;
>= UserTerminal.screenHeight - 16 => xy.y ← 0;
ENDCASE;
UserTerminal.cursor^ ← xy;
IF initTTY.CharsAvailable[] > 0 THEN {
[] ← initTTY.GetChar[]; -- discard first char, save type-ahead
EXIT};
Process.Pause[((Random[] MOD 8) * ticksPerSecond) / 4];
IF powerOff ~= 0 AND
fellAsleep + powerOff <= System.SecondsSinceEpoch[System.GetGreenwichMeanTime[]] THEN
ProcessorFace.PowerOff[];
UserTerminal.SetCursorPattern[cursor^]; -- in case some running program messed it up.
ENDLOOP;
SpecialTerminal.EnableCursorTracking[];
UserTerminal.SetCursorPattern[oldCursor];
[] ← UserTerminal.SetBackground[white];
[] ← UserTerminal.SetState[on];
IF actionProc[] THEN EXIT;
ENDLOOP;
SpecialTerminal.TurnOff[];
};
-- I/O utilities --
GetCedarVersion: PROC RETURNS [v: LONG STRING, versionLength: CARDINAL] = {
Append: Format.StringProc = {LongString.AppendString[v, s]};
v ← Heap.systemZone.NEW[StringBody[9+5+1+5+1+5+4+14]];
"ISLCedar nnnnn.mmmmm.ppppp of dd-mmm-yy hh:mm"
Format.LongString["ISLCedar "L, Append]; Format.Decimal[CedarVersion.major, Append];
Format.Char['., Append]; Format.Decimal[CedarVersion.minor, Append];
IF CedarVersion.patch ~= 0 THEN
{Format.Char['., Append]; Format.Decimal[CedarVersion.patch, Append]};
versionLength ← v.length;
Format.LongString[" of "L, Append];
Format.Date[LOOPHOLE[CedarVersion.bootFileDate], noSeconds, Append];
};
PromptForCredentials: PROC [name, password: STRING] = {
parameters must be long enough (BodyDefs.maxRNameLength)
defaultRegistry: STRING = ".pa"L;
cancel: STRING = " XXX\N"L;
DO
initTTY.PutString["Name: "L];
[] ← GetInitializedString[name ! TTY.Rubout => {initTTY.PutString[cancel]; LOOP}];
FOR i: CARDINAL DECREASING IN [0..name.length) DO
IF name[i] = '. THEN EXIT;
REPEAT
FINISHED => {
initTTY.PutString[defaultRegistry];
String.AppendString[name, defaultRegistry];
};
ENDLOOP;
initTTY.PutString[" password: "L];
[] ← initTTY.SetEcho[FALSE];
[] ← initTTY.GetID[password
! TTY.Rubout => {[] ← initTTY.SetEcho[TRUE]; initTTY.PutString[cancel]; LOOP}];
[] ← initTTY.SetEcho[TRUE];
EXIT
ENDLOOP;
initTTY.PutCR[];
};
GetInitializedString: PROC [str: STRING] RETURNS [c: CHARACTER] = {
assumes echoing is on!
OPEN Ascii;
firstTime: BOOLEANTRUE;
Check: PROC [c: CHARACTER] RETURNS [yes: BOOLEAN] = {
IF firstTime THEN {
SELECT c FROM
ControlA, BS, ControlQ, ControlW, ControlX, CR, SP => NULL;
ENDCASE => {
THROUGH [0..str.length) DO initTTY.PutChar[BS] ENDLOOP;
str.length ← 0};
firstTime ← FALSE};
RETURN[c = SP OR c = CR]};
initTTY.PutString[str];
c ← initTTY.GetEditedString[str, Check, FALSE
! TTY.LineOverflow => RESUME[str ← String.StringBoundsFault[str]]
];
};
Confirm: PROC [message: STRINGNIL] RETURNS [BOOLEAN] = {
IF message ~= NIL THEN initTTY.PutString[message];
DO
SELECT initTTY.GetChar[] FROM
'y, 'Y, Ascii.SP, Ascii.CR, Ascii.ESC => {initTTY.PutLine[" Yes"L]; RETURN[TRUE]};
'n, 'N, Ascii.DEL => {initTTY.PutLine[" No"L]; RETURN[FALSE]};
ENDCASE;
ENDLOOP;
};
ConfirmForBringOver: SAFE PROC[in, out: IO.Handle, data: REF ANY,
msg: Rope.ROPE, dch: CHAR] RETURNS[CHAR] = CHECKED {
ch: CHAR;
bs: IO.Handle;
out.PutRope[msg];
DO
ENABLE IO.Signal => IF ec = Rubout THEN LOOP;
out.PutF["? "];
bs ← IF in.backingStream = NIL THEN in ELSE in.backingStream;
ch ← bs.GetChar[];
IF ch = '\n THEN ch ← dch;
ch ← Rope.Lower[ch];
RETURN[ch];
ENDLOOP;
};

-- Installation Driver --
DoInstallation: PROC [booting: BOOLEAN] RETURNS [worked: BOOLEANFALSE] = {
This following line must match the one in 'versionFile' and the front of the DF file selected by <'server','path'>.
expectedVersion: STRING = "// September 15, 1983 11:00 am"L;
expectedVersionSS: String.SubStringDescriptor ←
[expectedVersion, 0, expectedVersion.length];
versionFile: STRING = "Cedar.version"L;
TextFile: TYPE = DESCRIPTOR FOR PACKED ARRAY OF CHARACTER;
GetLine: PROC [t: TextFile, offset: CARDINAL]
RETURNS [ss: String.SubStringDescriptor] = {
ss ← [base: LOOPHOLE[BASE[t], STRING] - SIZE[StringBody[0]], offset: offset, length: 0];
FOR i: CARDINAL IN [offset..LENGTH[t]) UNTIL t[i] = Ascii.CR DO
REPEAT
FINISHED => ss.length ← i - offset;
ENDLOOP};
WithFileDo: PROC [file: STRING, proc: PROC [TextFile]] = {
cap: File.Capability = Directory.Lookup[file];
space: Space.Handle ←
Space.Create[size: Inline.LowHalf[File.GetSize[cap]-1], parent: Space.mds];
bytes: CARDINAL = Inline.LowHalf[Directory.GetProps[cap, file].byteLength];
Space.Map[space, [cap, 1]];
proc[DESCRIPTOR[Space.Pointer[space], bytes]];
Space.Delete[space]};
expectedCreation: System.GreenwichMeanTime; -- parsed contents of 'expectedVersion'
ParseExpectedVersion: PROC = INLINE {
temp: STRING ← Heap.systemMDSZone.NEW[StringBody[expectedVersion.length]];
notes: DateAndTimeUnsafe.Notes;
ss: String.SubStringDescriptor;
i: CARDINAL;
FOR i IN [0..expectedVersion.length) DO
IF expectedVersion[i] = Ascii.SP THEN EXIT;
REPEAT FINISHED => ERROR;
ENDLOOP;
FOR i IN [i..expectedVersion.length) DO
IF expectedVersion[i] ~= Ascii.SP THEN EXIT;
REPEAT FINISHED => ERROR;
ENDLOOP;
ss ← [expectedVersion, i, expectedVersion.length - i];
String.AppendSubString[temp, @ss];
[expectedCreation, notes] ← DateAndTimeUnsafe.Parse[temp];
IF ~(notes IN [normal..zoneGuessed]) THEN ERROR;
Heap.systemMDSZone.FREE[@temp]};
CheckInstalledSystemVersion: PROC RETURNS [ok: BOOLEANFALSE] = {
CheckVersionLine: PROC [text: TextFile] = {
ss: String.SubStringDescriptor ← GetLine[text, 0]; -- throw away line 1 (compatibility)
ss ← GetLine[text, ss.length+1];
ok ← String.EqualSubStrings[@ss, @expectedVersionSS]};
WithFileDo[versionFile, CheckVersionLine ! ANY => CONTINUE]};
PrintBootSwitches: PROC = {
initTTY.PutString["Pilot boot switches:"L];
IF PilotSwitches.switches = TemporaryBooting.defaultSwitches THEN
initTTY.PutString[" (default)"L]
ELSE {
switches: PACKED ARRAY TemporaryBooting.Switch OF BOOLEAN =
LOOPHOLE[PilotSwitches.switches];
FOR sw: TemporaryBooting.Switch IN [zero..y] DO
IF switches[sw] THEN {
initTTY.PutChar[Ascii.SP];
initTTY.PutChar[(IF sw <= nine THEN '0 ELSE 'A-10)+LOOPHOLE[sw]]};
ENDLOOP;
IF PilotSwitches.switches.z = down THEN initTTY.PutString[" Z"L];
};
initTTY.PutString["\N\N"L];
};
DoSTPOperation: PROC [server: STRING, proc: PROC [stp: STP.Handle]] = {
stp: STP.Handle ← NIL;
name: STRING ← [BodyDefs.maxRNameLength];
password: STRING ← [BodyDefs.maxRNameLength];
UserCredentialsUnsafe.GetUserCredentials[name, password];
DO
BEGIN
ENABLE STP.Error => {
SELECT code FROM
The following can happen only on STP.Open
noNameLookupResponse => initTTY.PutString["can't find server"L];
The following typically happen only on STP.Open, but can also happen on the specific operation.
noRouteToNetwork => initTTY.PutString["inaccessible"L];
connectionTimedOut => initTTY.PutString["not responding"L];
connectionRejected, connectionClosed => initTTY.PutString["busy"L];
ENDCASE => initTTY.PutString["(unexpected error -- see Levin)"L];
IF Confirm[", retry?"L] THEN RETRY ELSE EXIT};
herald: STRING;
IF stp ~= NIL THEN [] ← STP.Destroy[stp ! STP.Error => CONTINUE];
stp ← STP.Create[];
initTTY.PutString["Opening connection to "L];
initTTY.PutString[server]; initTTY.PutString["..."L];
herald ← STP.Open[stp, server];
initTTY.PutLine["open"L]; initTTY.PutLine[herald];
Storage.Free[herald];
BEGIN
ENABLE STP.Error => {
SELECT code FROM
IN STP.CredentialsErrors => {
initTTY.PutString["unacceptable credentials ("L];
initTTY.PutString[error]; -- the server's message
initTTY.PutLine[")"L];
PromptForCredentials[name, password];
RETRY};
connectionTimedOut => {initTTY.PutLine["(timeout)"L]; LOOP};
ENDCASE};
STP.Login[stp, name, password];
proc[stp];
END;
END;
STP.Close[stp ! STP.Error => CONTINUE];
EXIT
ENDLOOP;
IF stp ~= NIL THEN [] ← STP.Destroy[stp ! STP.Error => CONTINUE];
};
RetrieveDF: PROC [server, path: STRING] RETURNS [localName: STRINGNIL] = {
newestCreation: System.GreenwichMeanTime ← System.gmtEpoch;
newestVersion: STRING ← Heap.systemMDSZone.NEW[StringBody[5]]; -- initial size
remoteName: String.SubStringDescriptor ←
[base: path, offset: 0, length: path.length-2];
creation: System.GreenwichMeanTime;
RetrieveSpecificDF: PROC [stp: STP.Handle] = {
CheckIfInteresting: STP.ConfirmProcType = {
info: STP.FileInfo = STP.GetFileInfo[stp]; -- Note: storage for info^ is inside stp^
notes: DateAndTimeUnsafe.Notes;
threshold: LONG CARDINAL = MAX[
System.SecondsSinceEpoch[expectedCreation], System.SecondsSinceEpoch[newestCreation]];
answer ← do; localStream ← NIL;
[creation, notes] ← DateAndTimeUnsafe.Parse[info.create];
IF ~(notes IN [normal..zoneGuessed]) THEN RETURN;
IF localName = NIL THEN {
localName ← Heap.systemMDSZone.NEW[StringBody[info.body.length]];
String.AppendString[localName, info.body]};
IF System.SecondsSinceEpoch[creation] <= threshold THEN answer ← skip};
CheckIfProperFile: STP.CompletionProcType = {
SELECT what FROM
ok => {
info: STP.FileInfo = STP.GetFileInfo[stp]; -- Note: storage for info^ is inside stp^
CheckIfNewer: PROC [text: TextFile] = {
ss: String.SubStringDescriptor ← GetLine[text, 0];
IF String.EqualSubStrings[@ss, @expectedVersionSS] THEN {
IF newestVersion.length < info.version.length THEN {
Heap.systemMDSZone.FREE[@newestVersion];
newestVersion ← Heap.systemMDSZone.NEW[StringBody[info.version.length]]};
newestVersion.length ← 0;
String.AppendString[newestVersion, info.version];
newestCreation ← creation}};
WithFileDo[localName, CheckIfNewer]};
error => NULL; -- probably file not found; handle after Retrieve is complete
ENDCASE};
EnsureProperLocalFile: PROC RETURNS [ok: BOOLEANTRUE] = {
cap: File.Capability;
IF localName = NIL OR newestCreation = System.gmtEpoch THEN GO TO notFound;
cap ← Directory.Lookup[localName ! Directory.Error => GO TO notFound];
IF Directory.GetProps[cap, localName].createDate ~= newestCreation THEN {
remoteFile: STRING
Heap.systemMDSZone.NEW[StringBody[path.length-1+newestVersion.length]];
String.AppendString[remoteFile, path];
remoteFile.length ← remoteFile.length - 1; -- remove trailing *
String.AppendString[remoteFile, newestVersion];
STP.Retrieve[stp, remoteFile];
Heap.systemMDSZone.FREE[@remoteFile]};
initTTY.PutChar['!]; initTTY.PutLine[newestVersion];
Heap.systemMDSZone.FREE[@newestVersion];
EXITS
notFound => {initTTY.PutLine["not found!"L]; RETURN[FALSE]}};
-- Main body of RetrieveSpecificDF --
initTTY.PutString["Retrieving "]; initTTY.PutSubString[@remoteName];
initTTY.PutString["..."L];
STP.Retrieve[stp, path, CheckIfInteresting, CheckIfProperFile
! STP.Error => IF code IN STP.FileErrors THEN CONTINUE];
IF ~EnsureProperLocalFile[] AND localName ~= NIL THEN
Heap.systemMDSZone.FREE[@localName]};
-- Main body of RetrieveDF --
DoSTPOperation[server, RetrieveSpecificDF]};
useWorkingDir: BOOL ← PilotSwitches.switches.d = down;
GetPaths: PROC RETURNS[server, path, basicPath, fatPath: STRING] = {
debuggerVolume: BOOL = Volume.GetType[Volume.systemID] ~= normal;
regularServer: STRING = "Indigo"L;
regularPathDir: STRING = "<ISLCedar>Top>"L;
debuggingServer: STRING = "Indigo"L;
debuggingPathDir: STRING = "<PreISLCedar>Top>"L;
fullFront: STRING = "Cedar"L;
fullBack: STRING = ".df!*"L;
basicFront: STRING = "BasicCedar"L;
basicBack: STRING = ".df"L;
fatBack: STRING = "Fat.df"L;
client: STRING = "Client"L;
debugger: STRING = "Debugger"L;
serverLength, pathLength, basicPathLength, fatPathLength: CARDINAL;
IF longDialogue THEN useWorkingDir ← Confirm["BringOver from working directories?"L];
serverLength ← IF useWorkingDir THEN debuggingServer.length ELSE regularServer.length;
pathLength ← fullFront.length + fullBack.length +
(IF useWorkingDir THEN debuggingPathDir.length ELSE regularPathDir.length) +
(IF debuggerVolume THEN debugger.length ELSE client.length);
basicPathLength ← basicFront.length + basicBack.length +
(IF useWorkingDir THEN debuggingPathDir.length ELSE regularPathDir.length) +
(IF debuggerVolume THEN debugger.length ELSE client.length);
fatPathLength ← fullFront.length + fatBack.length +
(IF useWorkingDir THEN debuggingPathDir.length ELSE regularPathDir.length) +
(IF debuggerVolume THEN debugger.length ELSE client.length);
server ← Heap.systemMDSZone.NEW[StringBody[serverLength]];
String.AppendString[server, IF useWorkingDir THEN debuggingServer ELSE regularServer];
path ← Heap.systemMDSZone.NEW[StringBody[pathLength]];
basicPath ← Heap.systemMDSZone.NEW[StringBody[basicPathLength]];
fatPath ← Heap.systemMDSZone.NEW[StringBody[fatPathLength]];
IF useWorkingDir THEN {
String.AppendString[path, debuggingPathDir];
String.AppendString[basicPath, debuggingPathDir];
String.AppendString[fatPath, debuggingPathDir];
}
ELSE {
String.AppendString[path, regularPathDir];
String.AppendString[basicPath, regularPathDir];
String.AppendString[fatPath, regularPathDir];
};
String.AppendString[path, fullFront];
String.AppendString[basicPath, basicFront];
String.AppendString[fatPath, fullFront];
IF debuggerVolume THEN {
String.AppendString[path, debugger];
String.AppendString[basicPath, debugger];
String.AppendString[fatPath, debugger];
}
ELSE {
String.AppendString[path, client];
String.AppendString[basicPath, client];
String.AppendString[fatPath, client];
};
String.AppendString[path, fullBack];
String.AppendString[basicPath, basicBack];
String.AppendString[fatPath, fatBack];
};
DoBringOver: PROC [dfFileName, server, basicCedarPath, fatCedarPath: STRING] = {
switches: ARRAY CHAR['a .. 'z] OF BOOLALL[FALSE];
listOfFiles: LIST OF Rope.Text;
in, out: IO.Handle;
parm: STRING ← Heap.systemMDSZone.NEW[StringBody[60]];
ExpandString: PROC [ps: POINTER TO STRING] = {
ns: STRING ← Heap.systemMDSZone.NEW[StringBody[(ps^.maxlength*3)/2]];
String.AppendString[ns, ps^];
Heap.systemMDSZone.FREE[ps];
ps^ ← ns;
};
{ENABLE String.StringBoundsFault => {ExpandString[@parm]; RESUME[parm]};
prefix: STRING = " /a"L;
IF longDialogue AND Confirm["Do you want to force retrieval, even if create dates appear OK?"L] THEN {
String.AppendString[parm, "/f"L];
switches['f] ← TRUE;
};
IF ~((longDialogue OR useWorkingDir) AND Confirm["Do you want to confirm each file retrieval individually?"L]) THEN {
String.AppendString[parm, prefix];
switches['a] ← TRUE;
};
String.AppendChar[parm, Ascii.SP];
String.AppendString[parm, dfFileName];
listOfFiles ← LIST[ConvertUnsafe.ToRope[dfFileName]];
IF basicCedar THEN {
String.AppendString[parm, " ["L];
String.AppendString[parm, server];
String.AppendChar[parm, ']];
String.AppendString[parm, basicCedarPath];
listOfFiles ← CONS[RopeInline.InlineFlatten[IO.PutFR["[%s]%s", IO.string[server], IO.string[basicCedarPath]]], listOfFiles];
};
IF publicMachine THEN {
String.AppendString[parm, " ["L];
String.AppendString[parm, server];
String.AppendChar[parm, ']];
String.AppendString[parm, fatCedarPath];
listOfFiles ← CONS[RopeInline.InlineFlatten[IO.PutFR["[%s]%s", IO.string[server], IO.string[fatCedarPath]]], listOfFiles];
};
DO
ENABLE TTY.Rubout => {initTTY.PutLine[" XXX"L]; CONTINUE};
IF ~publicMachine AND Confirm["Do you want to bring over a personal DF file?"L] THEN {
userName: STRING ← [BodyDefs.maxRNameLength];
userDF: STRING ← Heap.systemMDSZone.NEW[StringBody[40]];
PersonalDFExists: PROC RETURNS [found: BOOLEANFALSE] = {
IF userDF[0] = '[ THEN {
FOR i: CARDINAL IN [1..userDF.length) DO
IF userDF[i] = '] THEN {
ss: String.SubStringDescriptor ← [userDF, 1, i-1];
server: STRING ← Heap.systemMDSZone.NEW[StringBody[ss.length]];
path: STRING;
CheckExtant: PROC [stp: STP.Handle] = {
Exists: STP.NoteFileProcType = {found ← TRUE; RETURN[continue: no]};
STP.Enumerate[stp, path, Exists]};
String.AppendSubString[server, @ss];
ss.offset ← i+1;
ss.length ← userDF.length - (ss.length+2);
path ← Heap.systemMDSZone.NEW[StringBody[ss.length]];
String.AppendSubString[path, @ss];
DoSTPOperation[server, CheckExtant];
EXIT};
ENDLOOP}};
UserCredentialsUnsafe.GetUserCredentials[userName, NIL];
FOR i: CARDINAL DECREASING IN [0..userName.length) DO
IF userName[i] = '. THEN {userName.length ← i; EXIT};
ENDLOOP;
{ENABLE String.StringBoundsFault => {ExpandString[@userDF]; RESUME[userDF]};
String.AppendString[userDF, "[Ivy]<"L];
String.AppendString[userDF, userName];
String.AppendChar[userDF, '>];
String.AppendString[userDF, userName];
String.AppendString[userDF, ".df"L];
initTTY.PutString["Personal DF file name: "L];
[] ← GetInitializedString[userDF ! TTY.Rubout => Heap.systemMDSZone.FREE[@userDF]];
initTTY.PutCR[];
};
IF PersonalDFExists[] THEN {
String.AppendChar[parm, Ascii.SP];
String.AppendString[parm, userDF];
listOfFiles ← CONS[ConvertUnsafe.ToRope[userDF], listOfFiles];
Heap.systemMDSZone.FREE[@userDF]}
ELSE {
initTTY.PutString[userDF];
initTTY.PutLine[" can't be found!"L];
LOOP}};
EXIT
ENDLOOP;
String.AppendChar[parm, Ascii.CR];
}; -- end scope of ENABLE
in ← IO.CreateProcsStream[IO.CreateRefStreamProcs[getChar: MyGetChar, endOf: MyEndOf, userAbort: MyUserAbort], NIL];
out ← IO.CreateProcsStream[IO.CreateRefStreamProcs[putChar: MyPutChar], NIL];
BringOverCall.CedarBringOver[listOfFiles: listOfFiles, usingListOfRopes: NIL,
switches: switches, useCIFS: FALSE, in: in, out: out, confirmData: NIL,
Confirm: ConfirmForBringOver];
Heap.systemMDSZone.FREE[@parm]};

publicMachine: BOOLFALSE;
DoInstallationInternal: ENTRY PROC RETURNS [timedOut: BOOLFALSE] = {
ENABLE UNWIND => NULL;
ucodeError: LONG STRING ← CedarInitPrivate.ValidateMicrocode[];
filesInstalled: BOOL = CheckInstalledSystemVersion[];
allIsWell: BOOL =
ucodeError = NIL AND booting AND filesInstalled AND ~(longDialogue OR useWorkingDir);
credentialsState: UserCredentialsUnsafe.State = UserCredentialsUnsafe.GetCredentialsState[];
SpecialTerminal.SetInputTimeout[Process.SecondsToTicks[IF booting THEN 60 ELSE 0]];
BEGIN
ENABLE SpecialTerminal.InputTimeout => GO TO inputTimeout;
IF ~allIsWell THEN {
SpecialTerminal.EnableTypescriptFile[];
[] ← SpecialTerminal.TurnOn[];
PrintBootSwitches[];
SELECT TRUE FROM
longDialogue => longDialogue ← Confirm["Long installation dialogue [Confirm]"L];
~booting => longDialogue ← Confirm["Do you want the long installation dialogue?"L];
ENDCASE;
IF ucodeError ~= NIL THEN ReportUCodeError[ucodeError];
IF longDialogue OR ~(filesInstalled OR useWorkingDir OR credentialsState ~= nameHint) THEN
publicMachine ← Confirm["Shall I configure this disk for use as a public machine?"L];
};
UserCredentials.Login[
[confirmCredentialsOverwrite: longDialogue, prohibitDiskProtection: publicMachine]];
EXITS
inputTimeout => {
IF ~allIsWell THEN {
SpecialTerminal.DisableTypescriptFile[];
SpecialTerminal.TurnOff[];
};
SpecialTerminal.SetInputTimeout[0];
RETURN[TRUE]
};
END; -- ENABLE
SpecialTerminal.SetInputTimeout[0];
IF booting THEN TerminalMultiplex.PermitDebuggerSwaps[]; -- swaps are initially disabled
IF allIsWell THEN {worked ← TRUE; RETURN};
IF longDialogue THEN
salvageLSD ← Confirm["Do you want to salvage the local system directory?"L];
ParseExpectedVersion[];
IF ~(worked ← ~longDialogue AND ~useWorkingDir AND filesInstalled) THEN
DO
dfFileName: STRING;
server, path, basicCedarPath, fatCedarPath: STRING;
CleanUp: PROC = {
Heap.systemMDSZone.FREE[@server];
Heap.systemMDSZone.FREE[@path];
Heap.systemMDSZone.FREE[@basicCedarPath];
Heap.systemMDSZone.FREE[@fatCedarPath];
};
IF (longDialogue OR useWorkingDir) AND
~Confirm["Do you want the automatic BringOver?"L] THEN {worked ← TRUE; EXIT};
[server, path, basicCedarPath, fatCedarPath] ← GetPaths[];
IF (dfFileName ← RetrieveDF[server, path]) ~= NIL THEN {
DoBringOver[dfFileName, server, basicCedarPath, fatCedarPath];
Heap.systemMDSZone.FREE[@dfFileName];
CleanUp[];
IF CheckInstalledSystemVersion[] THEN worked ← TRUE
ELSE
The installation has failed, either because BringOver didn't complete successfully or the release directory is screwed up.
initTTY.PutLine["Installation failed...I give up."L]}
ELSE {
pathSS: String.SubStringDescriptor ← [base: path, offset: 0, length: path.length - 2];
IF ~useWorkingDir AND Confirm["Did you mean to specify the D switch at boot time?"L]
THEN {
initTTY.PutLine["(D switch now set.)"L];
useWorkingDir ← TRUE;
CleanUp[];
LOOP
};
initTTY.PutString["Sorry, I can't continue without a version of "L];
initTTY.PutChar['[]; initTTY.PutString[server]; initTTY.PutChar[']];
initTTY.PutSubString[@pathSS]; initTTY.PutString[" stamped with "L];
initTTY.PutDate[expectedCreation, dateTime]; initTTY.PutCR[];
CleanUp[]};
EXIT
ENDLOOP;
SpecialTerminal.DisableTypescriptFile[];
IF ~(booting AND ~worked) THEN SpecialTerminal.TurnOff[];
};
-- Main body of DoInstallation --
WHILE DoInstallationInternal[].timedOut DO
WakeUp: PROC RETURNS [wake: BOOL] = {RETURN[TRUE]};
IF booting THEN SleepInternal[WakeUp]
ELSE Sleep[];
ENDLOOP;
};
MyGetChar: SAFE PROC[self: IO.Handle] RETURNS[CHAR] = TRUSTED {
RETURN[TTY.GetChar[initTTY]];
};

MyEndOf: SAFE PROC[self: IO.Handle] RETURNS[BOOL] = CHECKED {
RETURN[FALSE];
};

MyUserAbort: SAFE PROC[self: IO.Handle] RETURNS[BOOL] = TRUSTED {
RETURN[TTY.UserAbort[]];
};

MyPutChar: SAFE PROC[self: IO.Handle, char: CHAR] = TRUSTED {
TTY.PutChar[initTTY, char];
};

-- Terminal Handler --
doGreeting: BOOLTRUE;
InitializeSpecialVirtualTerminal: PROC = {
[] ← SpecialTerminal.TurnOn[];
TerminalMultiplex.RegisterInputController[SpecialTerminalController];
SpecialTerminal.TurnOff[];
};
SpecialTerminalController: TerminalMultiplex.InputController = {
SELECT action FROM
enable =>
IF ~SpecialTerminal.TerminalOn[] THEN {
nameStripe: LONG STRING ← GetCedarVersion[].v;
SpecialTerminal.TurnOnInternal[nameStripe];
Heap.systemZone.FREE[@nameStripe];
initTTY ← SpecialTerminal.tty;
IF doGreeting THEN PrintGreeting[];
};
disable =>
IF SpecialTerminal.TerminalOn[] THEN SpecialTerminal.TurnOffInternal[];
ENDCASE};
EnableGreeting: PROC = {doGreeting ← TRUE};
DisableGreeting: PROC = {doGreeting ← FALSE};
PrintGreeting: PROC = {
DMachines: TYPE = CedarVersion.MachineType[dolphin..dicentra];
machineNames: ARRAY DMachines OF STRING = [
"Dolphin"L, "Dorado"L, "Dandelion"L, "Dicentra"L];
PutNo: PROC [b: BOOLEAN] = INLINE {IF ~b THEN initTTY.PutString[" no"L]};
cedarVersion: LONG STRING ← GetCedarVersion[].v;
initTTY.PutChar[Ascii.FF];
initTTY.PutLongString[cedarVersion];
Heap.systemZone.FREE[@cedarVersion];
initTTY.PutCR[];
initTTY.PutDate[System.GetGreenwichMeanTime[], full];
initTTY.PutCR[];
initTTY.PutString[machineNames[CedarVersion.machineType]];
initTTY.PutString[" microcode version "];
initTTY.PutDecimal[CedarVersion.uCodeVersion];
initTTY.PutString[" of "L];
initTTY.PutDate[LOOPHOLE[CedarVersion.uCodeDate], dateOnly];
initTTY.PutChar[',];
PutNo[CedarVersion.uCodeFloatingPoint];
initTTY.PutString[" floating point,"L];
PutNo[CedarVersion.uCodeCedar];
initTTY.PutString[" Cedar support"L];
initTTY.PutCR[];
initTTY.PutCR[];
};
-- Microcode checkout --
ReportUCodeError: INTERNAL PROC [error: LONG STRING] = {
assumes special terminal is on.
cedarVersion: TTY.LongSubStringDescriptor ← [NIL, 0, 0];
[cedarVersion.base, cedarVersion.length] ← GetCedarVersion[];
initTTY.PutLongSubString[@cedarVersion];
Heap.systemZone.FREE[@cedarVersion.base];
initTTY.PutString[" won't run on this machine: "L];
initTTY.PutLongString[error]; Heap.systemZone.FREE[@error];
initTTY.PutCR[];
IF ~longDialogue OR ~Confirm["Want to continue anyway?"L] THEN
CedarInitPrivate.FatalError[unsuitableMachine];
};
-- ***************** --
-- *** Main Body *** --
-- ***************** --
Run: PUBLIC PROC = {NULL}; -- the start trap does it all.
{ENABLE ANY => CedarInitPrivate.FatalError[implementationBug];
InitializeSpecialVirtualTerminal[];
IF ~DoInstallation[booting: TRUE] THEN CedarInitPrivate.FatalError[installationFailed];
};
Now start up the rest of the world
IF basicCedar THEN CedarInitPrivate.DoLoading[]
ELSE {
START CedarInitSequence.StartCedarCore;
START CedarInitSequence.StartCedarUserInterface;
START CedarInitSequence.StartCedarTools;
};
END.
Edited on December 8, 1982 11:57 pm, by Levin
changes to: SleepInternal - ensure special terminal is on, DoInstallationInternal (local of DoInstallation) - reword "public machine" question
Edited on December 15, 1982 5:38 pm, by Levin
changes to: patch, DoInstallation - roll version stamp
Edited on June 15, 1983 9:08 am, by Wyatt
changes to: GetPaths - <(Pre)Cedar> -> <(Pre)ISL>
Edited on June 26, 1983 5:30 pm, by Wyatt
changes to: GetPaths - <(Pre)ISL> -> <(Pre)ISLCedar>