Last Edited by: teitelman, May 23, 1983 6:31 pm
DIRECTORY
AMEvents USING [CallDebugger],
Atom USING [MakeAtom, GetProp, PutProp],
CIFS USING [Error, Open, GetFC, read],
ConvertUnsafe USING [AppendRope, ToRope],
Directory USING [Lookup, GetProps, Error],
File USING [Capability, nullCapability],
FileIO USING [Open, OpenFailed],
IO USING [CR, EndOf, EndOfStream, SyntaxError, Close, Flush, GetBlock, GetIndex, GetLength, int, GetCedarToken, PutChar, PutF, PutRope, ROPE, rope, RIS, SetIndex, SP, STREAM, TAB, GetToken, WhiteSpace, SkipOver, UserAborted],
IOExtras USING [GetCedarScannerToken, FromTokenProc],
Loader USING [Instantiate, Start, Error],
PrincOps USING [ControlModule],
Process USING [GetCurrent],
Rope USING [Cat, Concat, Equal, Fetch, Find, IsEmpty, Length, Replace, Substr, Text],
RopeInline USING [NewText],
RTProcess USING [GetTotalPageFaults, StartWatchingFaults],
SafeStorage USING [NWordsAllocated],
ShowTime USING [GetMark, Microseconds, Show],
System USING [GreenwichMeanTime],
Time USING [Current],
TiogaOps USING [AddLooks, CreateSimplePattern, FirstChild, GetRope, GoToPreviousCharacter, InsertChar, IsComment, Location, Next, NodeSearch, Paste, Pattern, Ref, SaveSpanForPaste, ViewerDoc, SelectPoint, LastLocWithin],
TiogaExtraOps USING [GetFile],
UserExec USING [HistoryEvent, ExecHandle, CheckForAbort, UserAbort, UserAborted, GetTheFile, GetStreams, ErrorThisEvent, GetDefaultExecHandle],
UserExecExtras USING [CreateEvent, NewErrorThisEvent],
UserExecPrivate USING [AcquireExec, EventFailed, ReleaseExec, Prompt, UpdateFrameCache, ExecPrivateRecord, StripComments, CreateSubEvent, methodList, MethodList, GetPrivateStuff, BlinkIcon, HistoryEventPrivateRecord],
UserProfile USING [Boolean, CallWhenProfileChanges, ProfileChangedProc],
ViewerClasses USING [Viewer],
ViewerOps USING [FindViewer]
;
UserExecMiscImpl: CEDAR PROGRAM
IMPORTS AMEvents, Atom, CIFS, ConvertUnsafe, Directory, FileIO, IO, IOExtras, Loader, Rope, RopeInline, RTProcess, SafeStorage, ShowTime, Time, UserExec, Process, TiogaOps, TiogaExtraOps, UserExecExtras, UserExecPrivate, UserProfile, ViewerOps
EXPORTS UserExec, UserExecExtras, UserExecPrivate
= BEGIN OPEN IO;
Types
ExecHandle: TYPE = UserExec.ExecHandle;
HistoryEvent: TYPE = UserExec.HistoryEvent ;
connecting concrete and opaque types
ExecPrivateRecord: PUBLIC TYPE = UserExecPrivate.ExecPrivateRecord;
to access currentEvent, dontPrompt, continuation in DoIt, currentEvent in CorrectionEnabled
HistoryEventPrivateRecord: PUBLIC TYPE = UserExecPrivate.HistoryEventPrivateRecord;
processing individual events
DoIt: PUBLIC PROC [input: ROPE, exec: ExecHandle ← UserExec.GetDefaultExecHandle[], partOf: HistoryEvent ← NIL] = {
private: REF UserExecPrivate.ExecPrivateRecord;
execOwner: UNSAFE PROCESS;
event, subEvent: HistoryEvent;
privateEvent, privateSubEvent: REF UserExecPrivate.HistoryEventPrivateRecord;
abortIfSubEventFails: BOOLEAN;
start, current: INT ← 0;
length: INT;
mark: ShowTime.Microseconds ← 0;
t0: System.GreenwichMeanTime;
nWords: LONG CARDINAL ← 0;
nFaults: INT ← 0;
Release: PROC = TRUSTED { -- Process
IF exec # NIL AND private.execState # destroyed AND UserExecPrivate.ReleaseExec[exec] THEN {
IF private.process = Process.GetCurrent[] THEN ERROR;
private.eventState ← readyForNext;
IF private.execState = listening THEN UserExecPrivate.Prompt[private.eventNum, exec];
};
};
{ENABLE UNWIND => Release[];
ShowStats: PROC = {
IF showStats AND exec # NIL AND NOT private.dontPrompt THEN
{
out: STREAM = UserExec.GetStreams[exec].out;
nw: INT ← SafeStorage.NWordsAllocated[] - nWords;
t: System.GreenwichMeanTime;
seconds: LONG CARDINAL;
nf: INT;
Put: PROC [char: CHAR] RETURNS[BOOLFALSE] = {out.PutChar[char]};
out.PutF["*n {"];
TRUSTED {t ← Time.Current[]};
seconds ← t - t0;
IF seconds > 60 THEN {
out.PutF["%d minutes, %d seconds", int[seconds/60], int[seconds MOD 60]];
}
ELSE {
ShowTime.Show[from: mark, p: Put, places: 2];
out.PutRope[" seconds"];
};
IF nw > 0 AND nw < 10000000 THEN out.PutF[", %d words", int[nw]];
TRUSTED {nf ← RTProcess.GetTotalPageFaults[] - nFaults};
IF nf > 0 AND nf < 10000000 THEN out.PutF[", %d page faults", int[nf]];
out.PutChar['}];
};
};
IF exec # NIL THEN {
private ← UserExecPrivate.GetPrivateStuff[exec];
execOwner ← private.execOwner;
IF UserExecPrivate.AcquireExec[exec] THEN TRUSTED { -- Process
IF private.process = Process.GetCurrent[] THEN ERROR; -- since Read Eval Print acquires exec first, this must be an event coming in from somewhere else.
IF private.execState = notListening OR private.execState = dormant THEN {
IF partOf # NIL THEN privateEvent ← partOf.privateStuff;
UserExecPrivate.Prompt[
IF partOf # NIL THEN privateEvent.eventNum ELSE private.eventNum, -- if partof was specified, then use its eventNumber.
exec];
}
ELSE IF private.eventState = readyForNext THEN private.eventState ← running
ELSE ERROR;
UserExec.GetStreams[exec].out.PutRope[input];
};
};
event ← IF partOf # NIL THEN partOf ELSE UserExecExtras.CreateEvent[exec, input];
subEvent ← event;
privateEvent ← event.privateStuff;
privateSubEvent ← subEvent.privateStuff;
length ← Rope.Length[input];
break input up into segments delimited by cr or ;
DO
stream: STREAM;
substr: ROPENIL;
whiteSpace: BOOLEANTRUE;
UserExec.CheckForAbort[exec];
IF current = length THEN EXIT;
start ← current;
WHILE current < length DO
char: CHARACTER ← Rope.Fetch[input, current];
TerminatesAtCurrent: PROC RETURNS[BOOL] = {
count: INT ← start;
fromTokenProc: IOExtras.FromTokenProc = {
count ← count + token.next;
IF token.kind = tokenCOMMENT AND closure.proc[closure.data, token.next - 1] = '\n
THEN count ← count - 1; -- cr is (incorrectly) included in comment. without this check, test would say that CR is not a legitimate terminator in this case
};
stream ← RIS[input, stream];
IO.SetIndex[stream, start];
IF NOT Rope.Equal[IO.GetCedarToken[stream! IO.EndOfStream => GOTO Yes], "←"] THEN RETURN[TRUE];
IO.SetIndex[stream, start];
DO
IOExtras.GetCedarScannerToken[stream, fromTokenProc !
IO.SyntaxError => CONTINUE
];
-- current is one beyond the character just read. We want to know if that character, e.g. CR could be the terminator. Therefore, we want to test and see if the scan stopped just before that character.
IF count = current - 1 THEN GOTO Yes -- stopped just before the desired place.
ELSE IF count >= current THEN GOTO No;
ENDLOOP;
EXITS
No => RETURN[FALSE];
Yes => RETURN[TRUE];
};
current ← current + 1;
SELECT char FROM
SP => IF whiteSpace THEN start ← current; -- necessary (aesthetic) for compound events
'' => current ← current + 1; -- from the standpoint of terminating the input, ignore next character. Whether ' or ^ is interpreted as special for command line will have to wait until we decide if this is a command or an expression.
'^ =>
SELECT Rope.Fetch[input, current - 2] FROM
SP, '\n, '\t => current ← current + 1; -- compromise. ^{cr} could end a line consisting of a mesa expression. Therefore, only give ^ its special interpretation (a la Alto exec) when preceded by white space.
ENDCASE;
'\\ => current ← current + 1; -- from the standpoint of terminating the input, ignore next character.
CR, TAB => {
IF whiteSpace THEN {start ← current; LOOP}
ELSE IF start = 0 AND current = length THEN substr ← input -- typical case
ELSE IF current = length OR TerminatesAtCurrent[] THEN substr ← Rope.Substr[base: input, start: start, len: current - start]
ELSE LOOP;
abortIfSubEventFails ← FALSE;
EXIT;
otherwise, keep going, e.g. CR is in middle of rope. current = length check says if this is the end of the rope, no point in calling ProperlyTerminated
};
'; => {
IF current = length OR TerminatesAtCurrent[] THEN {
substr ← Rope.Concat[Rope.Substr[base: input, start: start, len: current - start - 1], "\n"]; -- convert ; to CR so commands can all assume they are given a single line terminated by a CR.
abortIfSubEventFails ← TRUE;
EXIT;
};
otherwise, keep going, e.g. ; is in middle of rope.
};
ENDCASE => whiteSpace ← FALSE;
REPEAT
FINISHED => substr ← Rope.Substr[input, start, current]; -- e.g. terminate in ?
ENDLOOP; -- of WHILE loop that breaks into segments.
process substr
BEGIN
ENABLE {
IO.UserAborted => {
privateEvent.state ← aborted;
privateSubEvent.state ← aborted;
ShowStats[];
}; -- let error go through
UserExec.ErrorThisEvent => {
IF NOT Rope.IsEmpty[msg] THEN UserExec.GetStreams[exec].out.PutF["*n*e%g*s", rope[msg]];
privateEvent.state ← causedAnError;
privateSubEvent.state ← causedAnError;
IF exec.viewer.iconic THEN UserExecPrivate.BlinkIcon[exec.viewer];
ShowStats[];
IF NOT abortIfSubEventFails THEN LOOP; -- and go on with next subevent.
}; -- otherwise let error go through.
UserExecExtras.NewErrorThisEvent => {
IF NOT Rope.IsEmpty[msg] THEN UserExec.GetStreams[exec].out.PutF["*n*e%g*s", rope[msg]];
privateEvent.state ← causedAnError;
privateSubEvent.state ← causedAnError;
UserExecPrivate.EventFailed[event: event, offender: offender];
IF exec.viewer.iconic THEN UserExecPrivate.BlinkIcon[exec.viewer];
ShowStats[];
IF NOT abortIfSubEventFails THEN LOOP; -- and go on with next subevent.
}; -- otherwise let error go through.
UNWIND => {
privateEvent.state ← causedAnError;
privateSubEvent.state ← causedAnError;
IF exec.viewer.iconic AND private.execState # dormant THEN UserExecPrivate.BlinkIcon[exec.viewer];
};
};
inRopeStream: STREAM = RIS[rope: substr];
line: ROPE;
firstToken: ROPE;
firstToken ← IO.GetToken[inRopeStream];
IF Rope.IsEmpty[firstToken] THEN
{IF event # NIL AND event.subEvents = NIL AND current = length AND exec # NIL THEN private.continuation ← TRUE;
LOOP; -- white space on line in compound event.
};
IF event # NIL AND (event.subEvents # NIL OR current # length OR input # event.input) THEN { -- second case says this is a compound event. third says came from command file, where input field is @file and input (obtained from private.input) is the expansion
subEvent ← UserExecPrivate.CreateSubEvent[event: event, input: substr];
privateSubEvent ← subEvent.privateStuff;
UserExec.GetStreams[exec].out.PutF["*n"]; -- if previous event caused some output, want this to go on fresh line. See comments in userexecimpl regarding LogNewLine as to why just don't call NewLine directly.
};
line ← UserExecPrivate.StripComments[event, substr];
IF line # substr THEN -- some comments
{[] ← RIS[rope: line, oldStream: inRopeStream];
IO.SkipOver[inRopeStream, IO.WhiteSpace];
IF inRopeStream.EndOf[] THEN {privateSubEvent.state ← completed; LOOP}; -- nothing there but a comment.
};
subEvent.commandLine ← line;
subEvent.commandLineStream ← inRopeStream;
mark ← ShowTime.GetMark[];
nWords ← SafeStorage.NWordsAllocated[];
TRUSTED {t0 ← Time.Current[]; nFaults ← RTProcess.GetTotalPageFaults[]};
IF privateSubEvent.showInput THEN UserExec.GetStreams[exec].out.PutF["*n>%g", rope[line]];
FOR lst: UserExecPrivate.MethodList ← UserExecPrivate.methodList, lst.rest UNTIL lst = NIL DO
subEvent.commandLine ← line;
[] ← RIS[rope: line, oldStream: subEvent.commandLineStream]; -- load commandLineStream. Have to do it each time because the method might read from the commandLine before it determines that it is not applicable.
IF lst.first.proc[event: subEvent, exec: exec, clientData: lst.first.clientData] THEN
EXIT;
REPEAT
FINISHED => ERROR UserExecExtras.NewErrorThisEvent[event: subEvent, msg: Rope.Concat[firstToken, " not a command.\n"], offender: firstToken];
ENDLOOP; -- methodlist loop
END; -- of process substr.
ShowStats[];
privateSubEvent.state ← completed;
ENDLOOP; -- substr loop
privateEvent.state ← completed;
Release[];
};
}; -- DoIt
EventFailed: PUBLIC PROC[event: HistoryEvent, msg: ROPE ← NIL, offender: ROPENIL] = {
privateEvent: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
IF NOT Rope.IsEmpty[msg] THEN ERROR UserExecExtras.NewErrorThisEvent[event, msg, offender]
ELSE privateEvent.offender ← offender;
};
RopeFromCMFile: PUBLIC PROC [file: ROPE, event: HistoryEvent, exec: ExecHandle] RETURNS[contents: ROPE, name: ROPE] =
{ENABLE FileIO.OpenFailed => {
SELECT why FROM
fileNotFound =>
{
name ← UserExec.GetTheFile[file: file, defaultExt: "cm", event: event, exec: exec];
IF name # NIL THEN {contents ← RopeFromFile[name]; CONTINUE};
name ← UserExec.GetTheFile[file: file, defaultExt: "commands", event: event, exec: exec];
IF name # NIL THEN {contents ← RopeFromFile[name]; CONTINUE};
};
illegalFileName => NULL;
ENDCASE => REJECT;
ERROR UserExecExtras.NewErrorThisEvent[event: event, msg: Rope.Concat[fileName, " not found"], offender: fileName];
};
length: INT;
IF Rope.Fetch[file, 0] = '@ THEN file ← Rope.Substr[file, 1]; -- strip off @
length ← Rope.Length[file];
IF length = 0 THEN RETURN;
IF Rope.Fetch[file, length - 1] = '@ THEN file ← Rope.Substr[base: file, len: length - 1]; -- strip off trailing @
first try just filename
name ← file;
contents ← NIL;
contents ← RopeFromFile[fileName: file ! FileIO.OpenFailed =>
IF why = fileNotFound AND Rope.Find[file, "."] = -1 THEN
{name ← Rope.Concat[file, ".cm"]; CONTINUE}
];
IF contents # NIL THEN RETURN;
no extension specified, try .cm
contents ← RopeFromFile[fileName: name ! FileIO.OpenFailed =>
IF why= fileNotFound THEN
{name ← Rope.Concat[file, ".commands"]; CONTINUE}
];
IF contents # NIL THEN RETURN;
no extension specified, try .commands
contents ← RopeFromFile[fileName: name];
};
Think about using RopeIO
RopeFromFile: PROC [fileName: ROPE] RETURNS [value: ROPE] = TRUSTED { -- LOOPHOLE
handle: IO.STREAM ← FileIO.Open[fileName: fileName, accessOptions: read, createOptions: oldOnly];
length: LONG INTEGER ← handle.GetLength[];
text: Rope.Text ← RopeInline.NewText[length];
[] ← handle.GetBlock[LOOPHOLE[text, REF TEXT]];
IO.Close[handle];
RETURN[text];
};
StripComments: PUBLIC PROC [event: UserExec.HistoryEvent, rope: ROPE] RETURNS [ROPE] = {
pos1, pos2: INT ← 0;
WHILE (pos1 ← Rope.Find[s1: rope, s2: "//", pos1: pos1]) # -1 DO
pos2 ← Rope.Find[s1: rope, s2: "\n", pos1: pos1];
IF pos2 = -1 THEN pos2 ← Rope.Length[rope];
rope ← Rope.Replace[base: rope, start: pos1, len: pos2 - pos1 + 1];
ENDLOOP;
IF Rope.Find[s1: rope, s2: "//"] # -1 THEN UserExec.ErrorThisEvent[event, "// convention for comments no longer implemented. Use -- instead."];
pos1 ← 0;
WHILE (pos1 ← Rope.Find[s1: rope, s2: "--", pos1: pos1]) # -1 DO
pos3: INT ← Rope.Find[s1: rope, s2: "--", pos1: pos1 + 2];
pos2 ← Rope.Find[s1: rope, s2: "\n", pos1: pos1];
IF pos2 = -1 THEN pos2 ← Rope.Length[rope];
IF pos3 = -1 THEN pos3 ← Rope.Length[rope] ELSE pos3 ← pos3 + 2;
rope ← Rope.Replace[base: rope, start: pos1,
len: MIN[pos2, pos3] - pos1];
ENDLOOP;
RETURN[rope];
};
CorrectionDisabled: PUBLIC PROC[event: HistoryEvent] RETURNS[disabled: BOOL] = {
RETURN[IF event = NIL THEN FALSE ELSE event.dontCorrect];
};
looking up declarations in file
PrintDeclFromSource: PUBLIC PROC [target: ROPE, file: ROPE, exec: UserExec.ExecHandle] RETURNS [value: BOOLEAN] = {
out: IO.STREAM = UserExec.GetStreams[].out;
fileAtom: ATOM = Atom.MakeAtom[file];
doc: TiogaOps.Ref;
viewer: ViewerClasses.Viewer;
pattern: TiogaOps.Pattern;
start, end: TiogaOps.Location;
found, inline: BOOL;
r: ROPE;
stream: IO.STREAM;
inner: PROC [root: TiogaOps.Ref] = {
TRUSTED {doc ← LOOPHOLE[Atom.GetProp[atom: fileAtom, prop: $Root]]};
IF doc # NIL THEN NULL
ELSE IF (viewer ← ViewerOps.FindViewer[file]) # NIL THEN doc ← TiogaOps.ViewerDoc[viewer]
ELSE Atom.PutProp[atom: fileAtom, prop: $Root, val: doc ← TiogaExtraOps.GetFile[file ! CIFS.Error => CONTINUE]];
IF doc = NIL THEN {value ← FALSE; RETURN};
pattern ← TiogaOps.CreateSimplePattern[target]; -- does CreateSimplePattern ignore comments?
start ← [doc, 0];
DO
PrintChildren: PROC [node: TiogaOps.Ref, onlyComments: BOOLFALSE] = {
child: TiogaOps.Ref ← TiogaOps.FirstChild[node];
UserExec.CheckForAbort[exec];
DO
IF child = NIL THEN RETURN
ELSE IF (onlyComments OR NOT inline) AND NOT TiogaOps.IsComment[child] THEN RETURN
ELSE {
IF Rope.IsEmpty[TiogaOps.GetRope[child]] THEN onlyComments ← TRUE
idea is to avoid printing out a procedure which happens to be a child of this node but do want to print out inline definitions (non-comment children) and do want to print out comments that are separated by empty nodes. Thus as soon as you see an empty node, only consider comments subsequently.
ELSE Show[child];
PrintChildren[child, onlyComments];
};
child ← TiogaOps.Next[child];
ENDLOOP;
};
Show: PROC [node: TiogaOps.Ref, start: INT ← 0, end: INT ← -1] = {
r: ROPE = TiogaOps.GetRope[node];
len: INT = Rope.Length[r];
UserExec.CheckForAbort[exec];
IF end = -1 THEN end ← len;
TiogaOps.InsertChar['\n];
TiogaOps.GoToPreviousCharacter[]; -- If we are at the end of the typescript, Paste will act like a stuff, which is not what we want
TiogaOps.SaveSpanForPaste[startLoc: [node, start], endLoc: [node, end]];
TiogaOps.Paste[];
IF TiogaOps.IsComment[node] THEN TiogaOps.AddLooks["c"];
TiogaOps.SelectPoint[viewer: exec.viewer, caret: TiogaOps.LastLocWithin[TiogaOps.ViewerDoc[exec.viewer]]]; -- go to end. assumes that only one node in typescript.
ELSE {
out.PutRope[IF start = 0 AND end = len THEN r ELSE Rope.Substr[base: r, start: start, len: end - start]];
out.PutChar['\n];
};
};
i: INT;
UserExec.CheckForAbort[exec];
[found, start, end] ← TiogaOps.NodeSearch[pattern: pattern, startLoc: start, endLoc: start];
IF NOT found THEN {value ← FALSE; RETURN};
r ← TiogaOps.GetRope[start.node];
IF TiogaOps.IsComment[start.node] THEN { -- work around until CreateSimplePattern can take comment argument, or CreateGeneralPattern can take rope argument
start.where ← Rope.Length[r]; -- skip to end. StepForward no good as this would cause match not to succeed if the target was the first thing in the next node, e.g. IO.Put?
LOOP;
};
stream ← IO.RIS[r, stream];
IO.SetIndex[stream, end.where + 1];
i ← start.where;
WHILE i > 0 DO
i ← i - 1;
SELECT Rope.Fetch[r, i] FROM
'\n, '; => EXIT;
' => LOOP;
ENDCASE => GOTO NotDecl;
REPEAT
NotDecl => {start ← end; LOOP};
ENDLOOP;
DO
token: ROPE = IO.GetCedarToken[stream ! IO.EndOfStream => GOTO NotDecl];
IF Rope.Equal[token, ":"] THEN {start.where ← IO.GetIndex[stream]; EXIT}; -- Yes
IF Rope.Equal[token, ","] THEN {[] ← IO.GetCedarToken[stream ! IO.EndOfStream => GOTO NotDecl]; LOOP}; -- e.g. Foo, Fie: type = ...
GOTO NotDecl;
REPEAT
NotDecl => {start ← end; LOOP};
ENDLOOP;
out.Flush[];
IF start.node # TiogaOps.FirstChild[doc] THEN { -- node structure being used
inline ← TiogaOps.NodeSearch[pattern: TiogaOps.CreateSimplePattern["INLINE"], startLoc: start, endLoc: TiogaOps.LastLocWithin[start.node]].found;
Show[start.node, start.where];
PrintChildren[start.node];
}
ELSE {
end: INT = FindEnd[r, start.where];
inline ← TiogaOps.NodeSearch[pattern: TiogaOps.CreateSimplePattern["INLINE"], startLoc: start, endLoc: [start.node, end]].found;
Show[start.node, start.where, end];
};
TiogaOps.SelectPoint[viewer: exec.viewer, caret: TiogaOps.LastLocWithin[root]]; -- go to end. assumes that only one node in typescript.
value ← TRUE;
RETURN;
ENDLOOP;
};
TiogaOps.CallWithLocks[proc: inner, root: TiogaOps.ViewerDoc[exec.viewer]]; -- check when bill is here as to why this locks up
inner[TiogaOps.ViewerDoc[exec.viewer]];
}; -- of PrintDeclFromSource
FindEnd: PROC [nodeRope: ROPE, start: INT] RETURNS[end: INT] = {
i: INT;
inComment: BOOLFALSE;
blankLine: BOOLFALSE;
thisChar, lastChar: CHARACTER;
i ← Rope.Find[nodeRope, ";", start] + 1;
IF i = -1 THEN RETURN[Rope.Length[nodeRope]];
DO
lastChar ← thisChar;
thisChar ← Rope.Fetch[nodeRope, i];
i ← i + 1;
SELECT thisChar FROM
'- => {
blankLine ← FALSE;
IF lastChar = '- THEN inComment ← NOT inComment;
end ← i -1;
};
'\n => {
IF blankLine THEN RETURN; -- blank line, usually indicates end of commented area. Subsequent comments between here and end probably refer to what follows.
blankLine ← TRUE;
inComment ← FALSE;
};
' , '\t => NULL;
ENDCASE => {
blankLine ← FALSE;
IF ~inComment THEN RETURN;
end ← i -1;
}; -- anything seen outside of a comment means terminate.
ENDLOOP;
};
running bcds
FileNotFound: PUBLIC SIGNAL [name: ROPE, defaultExt: ROPENIL] RETURNS [shouldBe: ROPE] = CODE;
RunBCDFile: PUBLIC PROCEDURE[fileName: ROPE, fileCapability: File.Capability ← File.nullCapability, callDebuggerFirst: BOOLFALSE, out: STREAM] RETURNS[name: ROPE, error: ROPE] = {
ENABLE
FileNotFound => RESUME[SIGNAL FileNotFound[name: fileName, defaultExt: "bcd"]];
warnings: ROPE;
IF fileCapability # File.nullCapability THEN name ← fileName
ELSE IF Rope.Find[s1: fileName, s2: "."] = -1
THEN name ← Rope.Concat[fileName, ".bcd"]
ELSE name ← fileName;
[name, error, warnings] ← LoadAndGo[name, fileCapability, callDebuggerFirst];
IF error # NIL THEN
error ← Rope.Cat[error, ": ", fileName]
ELSE {
IF warnings # NIL THEN out.PutF["*n*m%g*s\n", rope[warnings]];
out.PutF["*nLoaded and started: %g\n", rope[name]];
};
};
LoadAndGo: PROC [fileName: ROPE, fileCapability: File.Capability, callDebuggerFirst: BOOLFALSE] RETURNS [name, error, warnings: ROPE] = TRUSTED { -- ConvertUnsafe
ls: LONG STRING = [100];
cm: PrincOps.ControlModule;
unboundImports: BOOLEAN;
IF fileCapability = File.nullCapability THEN {
IF Rope.Find[fileName, ">"] # -1 OR Rope.Find[fileName, "/"] # -1 THEN { -- use cifs
err: ROPE;
fileCapability ← CIFS.GetFC[CIFS.Open[name: fileName, mode: CIFS.read ! CIFS.Error => TRUSTED {
err ← error;
CONTINUE;
};
]];
error ← err;
}
ELSE {
ConvertUnsafe.AppendRope[to: ls, from: fileName];
fileCapability ← Directory.Lookup[ls ! Directory.Error => {
SELECT type FROM
invalidFileName => error ← "Illegal file name";
fileNotFound => {
fileName ← NARROW[SIGNAL FileNotFound[NIL, NIL]]; -- going to be caught in RunBCDFile and the appropriate arguments to the signal filled in .
IF fileName # NIL THEN {
ls.length ← 0;
ConvertUnsafe.AppendRope[to: ls, from: fileName];
RETRY;
};
error ← "Couldn't find a runnable file named";
};
ENDCASE => error ← "Lookup failed on";
CONTINUE;
}
];
};
};
IF error = NIL THEN [cm, unboundImports] ← Loader.Instantiate[file: fileCapability, offset: 1, codeLinks: TRUE ! Loader.Error => {
error ← SELECT type FROM
invalidBcd => "Invalid Bcd",
fileNotFound => "File Not Found",
versionMismatch => "Version MisMatch",
loadStateFull => "Load State Full, Can't Load",
insufficientVM => "Insufficient VM",
ENDCASE => ERROR;
IF message # NIL THEN error ← Rope.Cat[error, ": ", ConvertUnsafe.ToRope[LOOPHOLE[message, LONG STRING]]];
CONTINUE;
}
];
IF error = NIL THEN {
IF ls.length # 0 THEN [] ← Directory.GetProps[fileCapability, ls ! Directory.Error => CONTINUE];
name ← IF ls.length # 0 THEN ConvertUnsafe.ToRope[ls] -- GetProps writes the full name into the long string.
ELSE fileName;
};
IF error = NIL THEN {
IF callDebuggerFirst THEN AMEvents.CallDebugger[Rope.Concat["Loaded ", name]];
Loader.Start[cm ! ABORTED => {error ← "Execution Aborted"; CONTINUE}];
};
UserExecPrivate.UpdateFrameCache[];
IF unboundImports THEN warnings ← "(there are unbound imports)";
};
printing statistics
showStats: PUBLIC BOOLEANFALSE;
SetShowStats: UserProfile.ProfileChangedProc = TRUSTED { -- RTProcess
showStats ← UserProfile.Boolean["ShowStatistics", FALSE];
IF showStats THEN RTProcess.StartWatchingFaults[];
};
UserProfile.CallWhenProfileChanges[SetShowStats];
END. -- of UserExecMiscImpl
August 20, 1982 1:37 pm fixed LoadAndGo to use Loader.Instantiate and Loader.Start instead of Runtime.RunConfig. 
Edited on December 14, 1982 11:40 pm, by Teitelman
changed catch phrase, eliminating ANY, moving corresponding stuff to UNWIND. problem with informational signals when planting breakpoints under DoIt
changes to: DoIt
Edited on ile userexecmiscimpl
compile userexecmisDecember 22, 1982 12:00 pm, by Teitelman
changes to: DIRECTORY, IMPORTS, DoIt
Edited on January 21, 1983 4:10 pm, by Teitelman
changes to: DoIt, Release (local of DoIt)
Edited on January 23, 1983 5:08 pm, by Teitelman
changes to: DoIt
Edited on March 6, 1983 2:42 pm, by Teitelman
changes to: DIRECTORY, DoIt, RopeFromCMFile
Edited on March 10, 1983 3:07 am, by Teitelman
changes to: DIRECTORY, EXPORTS, IMPORTS, DoIt, RopeFromCMFile
Edited on March 13, 1983 2:27 pm, by Teitelman
changes to: DoIt
Edited on March 31, 1983 3:32 pm, by Teitelman
changes to: DoIt
Edited on April 7, 1983 2:42 pm, by Teitelman
changes to: DIRECTORY, RunBCDFile, LoadAndGo, UserProfile, IMPORTS
Edited on April 15, 1983 3:27 pm, by Teitelman
changes to: DoIt
Edited on April 20, 1983 10:00 am, by Teitelman
changes to: DoIt, EventFailed, RopeFromCMFile, DIRECTORY, LoadAndGo, DIRECTORY, ShowStats (local of DoIt), DIRECTORY, IMPORTS, ShowStats (local of DoIt), DIRECTORY, ShowStats (local of DoIt)
Edited on May 13, 1983 1:03 pm, by Teitelman
changes to: LoadAndGo
Edited on May 23, 1983 6:31 pm, by Teitelman
changes to: ShowStats (local of DoIt)