MobControl.mesa
Copyright Ó 1985, 1986, 1987, 1989, 1990, 1991, 1992 by Xerox Corporation. All rights reserved.
Paul Rovner, January 11, 1984 4:19 pm
Russ Atkinson, March 7, 1985 1:02:15 am PST
Rick Beach, April 3, 1985 11:38:18 am PST
Satterthwaite on June 20, 1986 4:03:12 pm PDT
Doug Wyatt, March 13, 1992 4:31 pm PST
Andy Litman August 2, 1988 12:03:47 pm PDT
JKF March 29, 1990 9:54:17 am PST
Foote, June 28, 1991 10:32 am PDT
DIRECTORY
Alloc USING [Create, Chunkify, Destroy, Failure, Overflow, Reset, TableInfo],
Ascii USING [Lower],
BasicTime USING [GMT, Now, Period, ToNSTime],
CinderInterface USING [],
MobBindDefs USING [RelocHandle],
MobComData USING [data],
MobControlDefs USING [BindRoot, BuildSemanticEntries, LoadRoot, WriteMob, PrintMob, PrintRelocations, PrintSemanticEntries, PrintTree, MakeInstall],
MobDefs USING [BinderNTables, httype, MTNull, NullName, sstype, treetype, VersionStamp, nullLink],
MobErrorDefs USING [Finalize, GetModule, GetSti, Initialize],
MobFileDefs USING [BuildFileTable, EraseFileTable],
MobHashTypes USING [htTag],
MobUtilDefs USING [EnterFile, Init, Reset],
Commander USING [CommandProc, Register],
MobCommandUtil USING [Echo, Failed, GetNthPair, ListLength, PairList, Parse, SetExtension],
FileViewerOps USING [WaitUntilSaved, ShowLog],
MobHashOps USING [Finalize, Initialize],
IO USING [CreateStream, CreateStreamProcs, GetLineRope, int, Put1, PutChar, PutF, PutF1, PutRope, RIS, rope, STREAM, StreamProcs, StreamVariety, time],
Loader USING [BCDBuildTime],
OSMiscOps USING [MergeStamps, TimeToStamp],
MobP1 USING [InstallMobParseTable, Parse],
CinderSysOps USING [Close, Delete, Open, OpenKind],
Process USING [CheckForAbort, EnableAborts, GetPriority, Priority, SetPriority],
Rope USING [Cat, Equal, Fetch, Find, Flatten, Length, ROPE, Substr],
MobSymbols USING [stNull],
SystemVersion USING [release],
MobTree USING [Link],
MobTreeOps USING [PopTree, Finalize, Initialize],
UserProfile USING [Token, Boolean];
MobControl: MONITOR
IMPORTS Alloc, Ascii, BasicTime, MobControlDefs, MobErrorDefs, MobFileDefs, MobUtilDefs, Commander, MobCommandUtil, MobHashOps, IO, Loader, OSMiscOps, MobP1, Rope, MobTreeOps, MobComData, CinderSysOps, SystemVersion, UserProfile, FileViewerOps, Process
EXPORTS CinderInterface
= BEGIN
OPEN MobComData;
EquivalentRope: PROC[s1, s2: Rope.ROPE] RETURNS[BOOL] ~ {
RETURN[s1.Equal[s2, FALSE]]};
Command Gathering And Logging
log: IO.STREAM ¬ NIL;
SetLogStream: PROC ~ {
log ¬ CinderSysOps.Open["Cinder.log", $writeLog].stream;
IO.SetLength[log, 0];
};
LogRope: PROC[s: Rope.ROPE] ~ {log.PutRope[s]};
LogChar: PROC[c: CHAR] ~ {log.PutChar[c]};
LogNumber: PROC[n: INTEGER] ~ {log.Put1[IO.int[n]]};
LogCR: PROC[] = {log.PutChar['\012]};
renamedOutput: BOOL ¬ FALSE;
WriteCR: PROC[s: IO.STREAM] ~ {s.PutChar['\012]};
RepeatCommand: PROC[s: IO.STREAM] ~ {
WriteCR[s];
s.PutRope["Cinding "]; s.PutRope[data.sourceName];
IF renamedOutput THEN {s.PutRope[", Mob to "]; s.PutRope[data.mobName]};
IF data.copySymbols THEN {
s.PutRope[", symbols to "];
s.PutRope[IF data.symbolName = NIL THEN "Mob" ELSE data.symbolName]};
WriteCR[s]};
Error Logging
errorName: Rope.ROPE ¬ NIL;
errorStream: IO.STREAM ¬ NIL;
errorStreamProcs: REF IO.StreamProcs ¬ NIL;
SetErrorName: PROC ~ TRUSTED {
IF errorName = NIL THEN {
errorName ¬ MobCommandUtil.SetExtension[data.rootName, "errlog"]}
};
DummyErrorStream: PROC[
putProc: SAFE PROC[self: IO.STREAM, char: CHAR]] RETURNS[IO.STREAM] ~ {
IF errorStreamProcs = NIL THEN
errorStreamProcs ¬ IO.CreateStreamProcs[
variety: $output,
class: $DummyErrorStream,
putChar: putProc];
RETURN[IO.CreateStream[errorStreamProcs, NIL]]};
OpenErrorStream: PROC ~ {
IF errorName = NIL THEN SetErrorName[];
errorStream ¬ CinderSysOps.Open[errorName, $writeLog].stream;
IO.SetLength[errorStream, 0];
WriteHerald[errorStream, errorName];
RepeatCommand[errorStream]};
ErrorPut: SAFE PROC[self: IO.STREAM, char: CHAR] ~ TRUSTED {
IF errorStream = NIL THEN OpenErrorStream[];
errorStream.PutChar[char]};
ErrorDestroy: PROC ~ {
IF errorStream # NIL THEN {
[] ¬ CinderSysOps.Close[errorStream]; errorStream ¬ NIL}
};
WriteHerald: PROC[stream: IO.STREAM, id: Rope.ROPE] ~ {
now: BasicTime.GMT ~ BasicTime.Now[];
stream.PutF["Cedar %g Cinder of %g",
IO.int[SystemVersion.release.major],
IO.time[Loader.BCDBuildTime[]]
];
WriteCR[stream];
IF fbh = NIL AND feedback.create # NIL
THEN fbh ← feedback.create[system~"Cinder"L, herald~herald];
IF id.Length[]=0
THEN stream.PutF1["Started %g", IO.time[now]]
ELSE stream.PutF["%g -- %g", IO.rope[id], IO.time[now]];
WriteCR[stream]};
Logger: UNSAFE PROC [proc: UNSAFE PROC [ log: IO.STREAM ] ] = TRUSTED {
proc[data.errorStream] };
File Bookkeeping
GetRoot: PROC[s: Rope.ROPE] RETURNS[Rope.ROPE] ~ {
dotIndex: INT ¬ Rope.Find[s, "."];
IF dotIndex > -1 THEN s ¬ Rope.Substr[s, 0, dotIndex];
RETURN[s]};
Switches
StandardDefaults: PACKED ARRAY CHAR ['a..'z] OF BOOL ~ [
FALSE, -- A Copy all (code and symbols)
FALSE, -- B TRUE => make install proc call XR¬StartCedarModule
FALSE, -- C Copy code
FALSE, -- D Call debugger error
TRUE, -- E Make installation procs be extern rather than static
FALSE, -- F Unused
TRUE, -- G TRUE => errlog goes to cinder.log, FALSE => use root.errlog
FALSE, -- H TRUE => Link together a packaged world. The "MakeBoot" switch.
FALSE, -- I Unused
FALSE, -- J FALSE => old behaviour, ie -lxrc -lm, TRUE => no library search
FALSE, -- K Unused
FALSE, -- L Unused (used to be the lf/cr swtich - makedo still issues it, but it's obsolete)
FALSE, -- M MakeDo switch - if true => generate .c2c.c extension vs. .c
FALSE, -- N Unused
FALSE, -- O Unused
FALSE, -- P Pause after config with errors
FALSE, -- Q Generate .ld file with cc -pic
FALSE, -- R Generate .ld file with no -r option to ld
FALSE, -- S Copy symbols
FALSE, -- T Generate .ld file with cc -PIC
FALSE, -- U Unused
FALSE, -- V Do version checking on the input files
FALSE, -- W Pause after config with warnings
FALSE, -- X Copy compressed symbols (not implemented)
FALSE, -- Y Unused
FALSE];-- Z Unused
Command interface
binderBusy: BOOL ¬ FALSE;
busyChanged: CONDITION;
WaitForBinderFree: PROC = ENTRY {
ENABLE UNWIND => NULL;
WHILE binderBusy DO
TRUSTED { Process.EnableAborts[@busyChanged] };
WAIT busyChanged;
ENDLOOP;
binderBusy ¬ TRUE};
SetBinderFree: PROC = ENTRY {
binderBusy ¬ FALSE;
BROADCAST busyChanged};
Cind: Commander.CommandProc ~ CHECKED {
in: IO.STREAM ~ IO.RIS[cmd.commandLine];
out: IO.STREAM ~ cmd.out;
clientData: REF ~ cmd.procData.clientData;
[result: result] ¬ DoCind[in, out, clientData]; -- DKW asserts that msg is uninteresting
};
DoCind: PUBLIC SAFE PROC [in: IO.STREAM, out: IO.STREAM, clientData: REF]
RETURNS [result: REF ¬ NIL, msg: Rope.ROPE ¬ NIL] ~ TRUSTED {
results: MobCommandUtil.PairList;
switches: Rope.ROPE;
key, value: Rope.ROPE;
anyErrors, anyWarnings: BOOL ¬ FALSE;
priority: Process.Priority = Process.GetPriority[];
localPause: BOOL;
defaultSwitches: PACKED ARRAY CHAR['a..'z] OF BOOL ¬ StandardDefaults;
defaultDebugPass: CARDINAL ¬ CARDINAL.LAST;
localSwitches: PACKED ARRAY CHAR['a..'z] OF BOOL;
debugPass: CARDINAL;
useFileViewerOps: BOOL = clientData # $CinderServer;
Cleanup: PROC ~ TRUSTED {
Process.SetPriority[priority];
IF data.table # NIL THEN {Alloc.Destroy[data.table]; data.table ¬ NIL};
SetBinderFree[]};
in ¬ IO.RIS[
Rope.Cat[UserProfile.Token["Cinder.Switches"], " ", IO.GetLineRope[in]],
in];
WaitForBinderFree[];
data.sourceName ¬ data.mobName ¬ data.codeName ¬ data.symbolName ¬ NIL;
data.installName ¬ NIL;
data.op ¬ $bind;
data.table ¬ NIL;
log ¬ NIL;
{
ENABLE UNWIND => {
IF log # NIL THEN [] ¬ CinderSysOps.Close[log];
log ¬ NIL;
result ¬ $Failure;
msg ¬ "A";
Cleanup[]};
SetLogStream[];
WriteHerald[log, NIL];
Process.SetPriority[VAL[1]]; --Process.priorityBackground or Process.priorityUserBackground
main loop
DO {
Initialize: PROC ~ TRUSTED {
max: INT = LAST[NAT];
weights: ARRAY [0..MobDefs.BinderNTables) OF Alloc.TableInfo ¬ [
empirical (SDD) - these are MobDefs.Selector's
[0,4,max], -- trees
[MobHashTypes.htTag,2,max], -- hash table
[0,10,max], -- (packed) string table
[0,4,max], -- config table
[0,5,max], -- module table
[0,4,max], -- import table
[0,4,max], -- export table
[0,4,max], -- segment table
[0,2,max], -- file table
[0,1,max], -- semantic table
[0,4,max], -- context table
[0,4,max], -- name table
[0,4,max], -- external variable table
[0,2,max], -- space table
[0,4,max], -- frame pack table
[0,2,max], -- type table
[0,4,max], -- type table
[0,5,max], -- link fragment table
[0,1,max], -- ref literal and atom fragment table
[0,1,max]]; -- type fragment table
RepeatCommand[log];
data.errors ¬ data.warnings ¬ data.aborted ¬ FALSE;
data.nErrors ¬ data.nWarnings ¬ 0;
data.textIndex ¬ 0;
data.currentName ¬ MobDefs.NullName;
IF data.table = NIL THEN {
data.table ¬ Alloc.Create[weights~DESCRIPTOR[weights]];
(data.table).Chunkify[MobDefs.treetype]}
ELSE (data.table).Reset[];
MobHashOps.Initialize[data.table, MobDefs.httype, MobDefs.sstype];
MobTreeOps.Initialize[data.table];
MobUtilDefs.Init[data.table];
MobErrorDefs.Initialize[];
errorStream ¬ NIL};
Finalize: PROC ~ TRUSTED {
MobTreeOps.Finalize[];
MobHashOps.Finalize[];
MobErrorDefs.Finalize[];
MobUtilDefs.Reset[];
(data.table).Reset[];
anyErrors ¬ data.errors OR anyErrors;
anyWarnings ¬ data.warnings OR anyWarnings;
IF data.aborted THEN { LogRope["Cinding aborted"]; LogCR[]}
ELSE IF data.errors THEN { LogRope["Errors detected; Mob not written"]; LogCR[]}
ELSE {
IF data.nConfigs > 1 THEN {
LogNumber[data.nConfigs]; LogRope[" configs, "]};
LogNumber[data.nModules]; LogRope[" modules, "];
LogNumber[data.nImports]; LogRope[" imports, "];
LogNumber[data.nExports]; LogRope[" exports, "];
LogNumber[data.nPages]; LogRope[" pages, "];
LogNumber[BasicTime.Period[from: startTime, to: BasicTime.Now[]]];
LogRope[" seconds"];
LogCR[]};
IF errorStream # NIL THEN { LogRope["See "]; LogRope[errorName]; LogCR[] };
IF log # data.errorStream THEN ErrorDestroy[];
IF errorName = NIL THEN {
SetErrorName[];
IF NOT data.aborted THEN [] ¬ CinderSysOps.Delete[errorName];
};
[] ¬ CinderSysOps.Close[data.sourceStream];
[] ¬ CinderSysOps.Close[data.outputStream];
[] ¬ CinderSysOps.Close[data.installStream];
[] ¬ CinderSysOps.Close[data.ldStream];
IF data.nErrors # 0 OR data.aborted THEN [] ¬ CinderSysOps.Delete[data.mobName];
data.outputStream ¬ NIL;
IF feedback.finishItem # NIL THEN ...
IF data.nErrors=0
THEN out.PutRope["no errors"]
ELSE {
out.PutF1["%g error", IO.int[data.nErrors]];
IF data.nErrors#1 THEN out.PutChar['s]};
IF data.nWarnings=0
THEN NULL
ELSE {
out.PutF1[", %g warning", IO.int[data.nWarnings]];
IF data.nWarnings#1 THEN out.PutChar['s]};
out.PutRope[".\n"];
};
Debug: PROC [ printRel, printMob: BOOL ] ~ TRUSTED {
MobControlDefs.PrintTree[root];
MobControlDefs.PrintSemanticEntries[];
IF printRel THEN MobControlDefs.PrintRelocations[relocationHead];
IF printMob THEN MobControlDefs.PrintMob[]};
parsed: BOOL;
root: MobTree.Link;
first: BOOL ¬ TRUE;
relocationHead: MobBindDefs.RelocHandle;
startTime: BasicTime.GMT;
needFileTableErase: BOOL ¬ FALSE;
localSwitches ¬ defaultSwitches;
localPause ¬ FALSE;
debugPass ¬ defaultDebugPass;
renamedOutput ¬ FALSE;
data.aborted ¬ FALSE;
[data.sourceName, data.commandArgs, results, switches] ¬
MobCommandUtil.Parse[in
! MobCommandUtil.Failed => {GOTO badSyntax}];
IF data.sourceName = NIL AND switches = NIL THEN EXIT; -- done cinding
LogCR[];
LogRope["Command: "];
MobCommandUtil.Echo[
d~log, operator~data.sourceName, argList~data.commandArgs,
resultList~results, switches~switches];
IF data.sourceName = NIL THEN GOTO globalSwitches;
FOR n: CARDINAL IN [0..MobCommandUtil.ListLength[results]) DO
[key, value] ¬ MobCommandUtil.GetNthPair[list~results, n~n];
SELECT TRUE FROM
(key = NIL), EquivalentRope[key, "mob"] => {
data.mobName ¬ value; renamedOutput ¬ TRUE};
EquivalentRope[key, "code"] => {
data.codeName ¬ value; localSwitches['c] ¬ TRUE};
EquivalentRope[key, "symbols"] => {
data.symbolName ¬ value; localSwitches['s] ¬ TRUE};
ENDCASE => GO TO badSemantics;
ENDLOOP;
data.rootName ¬ GetRoot[
(IF data.mobName # NIL THEN data.mobName ELSE data.sourceName)];
IF switches # NIL THEN {
sense: BOOL ¬ TRUE;
length: INT ¬ switches.Length[];
FOR i: INT IN [0..length) DO
c: CHAR ~ switches.Fetch[i];
SELECT c FROM
'-, '~ => sense ¬ ~sense;
IN ['a..'z] => {localSwitches[c] ¬ sense; sense ¬ TRUE};
IN ['A..'Z] => {localSwitches[Ascii.Lower[c]] ¬ sense; sense ¬ TRUE};
IN ['1..'4] => {debugPass ¬ c-'0; sense ¬ TRUE};
ENDCASE;
ENDLOOP;
};
data.sourceName ¬ MobCommandUtil.SetExtension[data.sourceName, "config"];
IF useFileViewerOps
THEN FileViewerOps.WaitUntilSaved[data.sourceName, out
! ABORTED => {data.aborted ¬ TRUE; EXIT}];
IF data.mobName = NIL THEN data.mobName ¬ data.rootName;
data.mobName ¬ MobCommandUtil.SetExtension[data.mobName, "mob"];
data.copySymbols ¬ (localSwitches['s] OR localSwitches['x] OR localSwitches['a]);
data.dynamicLibrarySearch ¬ localSwitches['j];
data.pic ¬ localSwitches['q];
data.PIC ¬ localSwitches['t];
data.relocate ¬ localSwitches['r];
data.extern ¬ localSwitches['e];
data.cedarCoreConfig ¬ localSwitches['b];
data.buildPackagedWorld ¬ localSwitches['h];
IF data.installName = NIL THEN data.installName ¬ data.rootName;
data.useC2CExtension ¬ localSwitches['m];
data.installName ¬
MobCommandUtil.SetExtension[data.installName, IF localSwitches['m] THEN "c2c.c" ELSE "c"];
data.ldName ¬ MobCommandUtil.SetExtension[data.rootName, "ld"];
IF localSwitches['x] THEN
{ LogCR[]; LogRope["Symbol compression not available in this version"] };
IF data.copySymbols AND (data.symbolName # NIL) AND ~localSwitches['a] THEN {
data.symbolName ¬ MobCommandUtil.SetExtension[data.symbolName, "symbols"];
IF EquivalentRope[data.symbolName, data.mobName] THEN data.symbolName ¬ NIL;
};
out.PutRope["Cinding: "]; out.PutRope[data.rootName];
FOR c: CHAR IN ['a..'z] DO
IF localSwitches[c] # StandardDefaults[c] THEN {
IF first THEN {first ¬ FALSE; out.PutChar['-]};
IF StandardDefaults[c] THEN out.PutChar['~];
out.PutChar[c]};
ENDLOOP;
startTime ¬ BasicTime.Now[];
data.errorStream ¬ NIL;
data.outputStream ¬ NIL;
data.installStream ¬ NIL;
data.ldStream ¬ NIL;
data.sourceStream ¬ NIL;
BEGIN
sourcetime: BasicTime.GMT;
[data.sourceStream,, sourcetime] ¬ CinderSysOps.Open[data.sourceName, $read];
data.sourceVersion[0] ¬ LOOPHOLE[BasicTime.ToNSTime[sourcetime]];
END;
IF data.sourceStream = NIL THEN GOTO noSource;
data.outputStream ¬ CinderSysOps.Open[data.mobName, $write].stream;
data.installStream ¬ CinderSysOps.Open[data.installName, $write].stream;
data.ldStream ¬ CinderSysOps.Open[data.ldName, $write].stream;
data.logStream ¬ log;
data.errorStream ¬
IF localSwitches['g] THEN log ELSE DummyErrorStream[putProc~ErrorPut];
localPause ¬ localSwitches['p];
data.debug ¬ localSwitches['d];
localSwitches['g] ¬ localSwitches['p] ¬ localSwitches['d] ¬ FALSE;
data.objectStamp ¬ OSMiscOps.TimeToStamp[data.sourceVersion];
encode switches, cinder version (see MobLoad processing also)
data.objectStamp ¬ OSMiscOps.MergeStamps[
data.objectStamp, OSMiscOps.TimeToStamp[[0, LOOPHOLE[localSwitches]]]];
data.objectStamp ¬ OSMiscOps.MergeStamps[
data.objectStamp, OSMiscOps.TimeToStamp[data.binderVersion]];
Initialize[];
BEGIN
ENABLE {
MobErrorDefs.GetModule => RESUME [MobDefs.MTNull, 0, MobDefs.nullLink];
MobErrorDefs.GetSti => RESUME [MobSymbols.stNull];
Alloc.Overflow => RESUME[2];
Alloc.Failure => {
data.errors ¬ TRUE;
IF ~data.debug THEN {
LogRope["Storage Overflow"]; LogCR[]; GOTO Overflow}};
UNWIND => {IF needFileTableErase THEN MobFileDefs.EraseFileTable[]; Finalize[]};
};
needFileTableErase ¬ FALSE;
Process.CheckForAbort[];
out.PutRope[". "]; -- pass 1
[complete~parsed, nErrors~data.nErrors] ¬
MobP1.Parse[data.sourceStream, Logger, TRUE];
IF ~parsed THEN GO TO Failed;
IF data.nErrors > 0 THEN data.errors ¬ TRUE;
root ¬ MobTreeOps.PopTree[];
MakeInstall can be put here if there is no EXPORTS ALL
MobControlDefs.BuildSemanticEntries[root];
data.outputFti ¬ MobUtilDefs.EnterFile[LOOPHOLE[Rope.Flatten[data.mobName]]];
MobFileDefs.BuildFileTable[data.table];
needFileTableErase ¬ TRUE;
IF debugPass <= 1 THEN Debug[printRel~FALSE, printMob~FALSE];
Process.CheckForAbort[];
out.PutRope[". "]; -- pass 2
IF ~data.errors AND ~localSwitches['v]
THEN relocationHead ¬ MobControlDefs.LoadRoot[root];
IF ~data.errors AND ~localSwitches['v]
THEN MobControlDefs.MakeInstall[root];
IF debugPass <= 2 THEN Debug[printRel~TRUE, printMob~TRUE];
Process.CheckForAbort[];
out.PutRope[". "]; -- pass 3
IF ~data.errors AND ~localSwitches['v]
THEN MobControlDefs.BindRoot[relocationHead];
IF debugPass <= 3 THEN Debug[printRel~FALSE, printMob~TRUE];
Process.CheckForAbort[];
out.PutRope[". "]; -- pass 4
IF ~data.errors AND ~localSwitches['v]
THEN MobControlDefs.WriteMob[root];
MobFileDefs.EraseFileTable[];
EXITS
Overflow => NULL;
Failed => data.errors ¬ TRUE;
END;
Finalize[];
IF useFileViewerOps AND errorName#NIL THEN FileViewerOps.ShowLog[
fileName: errorName,
destroyIt: NOT(data.errors OR data.warnings),
createIconic: UserProfile.Boolean["Compiler.IconicLogs", FALSE],
blinkIfIconic: UserProfile.Boolean["Compiler.IconicLogs", FALSE]
];
data.sourceName ¬ data.mobName ¬ data.codeName ¬ data.symbolName ¬ NIL;
data.installName ¬ NIL;
errorName ¬ NIL;
EXITS
noSource => {
LogCR[];
LogRope["Can't open "];
LogRope[data.sourceName];
LogCR[];
IO.PutF1[out, " -- can't open %g\n", [rope[data.sourceName]] ];
data.errors ¬ anyErrors ¬ TRUE};
globalSwitches => {
sense: BOOL ¬ TRUE;
length: INT ¬ switches.Length[];
FOR i: INT IN [0..length) DO
c: CHAR ~ switches.Fetch[i];
SELECT c FROM
'-, '~ => sense ¬ ~sense;
IN ['a..'z] => {defaultSwitches[c] ¬ sense; sense ¬ TRUE};
IN ['A..'Z] => {defaultSwitches[Ascii.Lower[c]] ¬ sense; sense ¬ TRUE};
IN ['1..'5] => {defaultDebugPass ¬ c-'0; sense ¬ TRUE};
ENDCASE => EXIT;
ENDLOOP};
badSemantics => {
data.errors ¬ anyErrors ¬ TRUE;
LogCR[];
LogRope[" -- Illegal command"]};
};
IF data.aborted THEN EXIT; -- stop cinding
IF (data.errors OR (data.warnings AND localSwitches['w])) AND localPause THEN EXIT;
REPEAT
badSyntax => {anyErrors ¬ data.errors ¬ TRUE; LogRope["-- Illegal syntax"]};
ENDLOOP;
[] ¬ CinderSysOps.Close[log];
out.PutRope["End of cinding\n"]; -- DKW
SELECT TRUE FROM
data.aborted => { result ¬ $Failure; msg ¬ "A"; };
anyErrors => { result ¬ $Failure; msg ¬ "F"; };
anyWarnings => { result ¬ $Failure; msg ¬ "W"; };
ENDCASE => { result ¬ $Success; msg ¬ "S"; }; -- DKW
}; -- end of ENABLE UNWIND
Cleanup[];
};
Global cinder initialization
Init: PROC ~ {
data.binderVersion ¬ [0,0]; -- Cinder release
MobP1.InstallMobParseTable[];
Commander.Register["Cind", Cind, "Cind a list of configurations.", $Cinder];
Commander.Register["PCind", Cind, "Cind a list of configurations.", $Cinder];
};
Init[];
END.