file: PasInit.mesa
modified by Ramshaw, January 20, 1984 4:21 pm
written by McCreight, November 21, 1980 1:12 PM
Last changed by Pavel, May 29, 1985 8:51:16 pm PDT
May 29, 1985: Changed by Pavel to add the ability to export an interface from the bound BCD. If the name of a definitions file in the .mod file is followed by a star (*), then that interface is exported in the generated .config file. Said interface file must have been given as either ``external'' or ``forward''. Saying ``trash'' causes a type error.
DIRECTORY
FS USING [StreamOpen],
IO USING [PutFR, RIS, rope, STREAM, time],
PasPrivate,
PasPrivateVars,
Rope USING [Cat, Equal, Length];
PasInit: CEDAR PROGRAM IMPORTS
FS, IO, PasPrivate, PasPrivateVars, Rope
EXPORTS PasPrivate =
BEGIN OPEN PasPrivate, PasPrivateVars;
PascalStandardFileNames: PUBLIC ARRAY StandardFiles OF ROPE
["INPUT", "OUTPUT", "TTY", "?FILE1", "?FILE2"];
PascalStandardProcedureNames: PUBLIC ARRAY StandardProcedures OF ROPE
["HALT", "GET", "PUT", "RESET", "REWRITE", "READ", "READLN", "WRITE",
"WRITELN", "BREAK", "PACK", "UNPACK", "NEW", "DISPOSE", "PAGE", "RELEASE",
"ASSIGN", "CONCAT", "PUTCHAR", "GETFILENAME", "DATE", "TIME", "?PROC1",
"?PROC2", "?PROC3", "?PROC4", "?PROC5"];
PascalStandardFunctionNames: PUBLIC ARRAY StandardFunctions OF ROPE
["CLOCK", "ABS", "SQR", "SIN", "COS", "EXP", "LN", "SQRT", "ARCTAN", "ODD",
"ORD", "CHR", "PRED", "SUCC", "EOF", "EOLN", "EOPAGE", "CARD", "LOWERBOUND",
"UPPERBOUND", "MIN", "MAX", "FIRST", "LAST", "ROUND", "TRUNC", "LENGTH",
"GETCHAR", "?FN1", "?FN2", "?FN3", "?FN4", "?FN5"];
textFile: FileTypePtr;
configName: ROPE;
configQ: OutputQueuePtr;
makeFileQ: OutputQueuePtr ← NIL;
alfa, alfaIndexRange: TypePtr;
readySourceFileSeq: SourceFileSeqPtr ← NIL;
compilerSwitches: ROPE;
InitializeStandards: PUBLIC PROCEDURE=
BEGIN
s: Standards;
MakeType: PROCEDURE [name: ROPE, t: GeneralTypePtr]
RETURNS [IdentifierPtr] =
BEGIN
id: IdentifierPtr ← NewIdent[name: name];
id.type ← t;
id.class ← Z.NEW[IdentifierTail←[type[]]];
RETURN[id];
END; -- of MakeType
integerId ← MakeType["INTEGER", integer];
realId ← MakeType["REAL", real];
charId ← MakeType["CHAR", char];
[] ← MakeType["ASCII", charId];
booleanId ← MakeType["BOOLEAN", boolean];
stringId ← MakeType["STRING", string];
alfaIndexRange ← Z.NEW[subRange Type ←
[subRange[hostType: integer, lower: 1, upper: 10]]];
alfa ← Z.NEW[array Type ←
[array[
aIsPacked: TRUE, aElType: char,
aIxType: alfaIndexRange]]];
[] ← MakeType["ALFA", alfa];
textFile ← Z.NEW[file Type ←
[file[fileIsPacked: TRUE, textFile: TRUE, fileType: charId]]];
[] ← MakeType["TEXT", textFile];
maxIntegerId ← NARROW[NewIdent[name: "MAXINT"], ConstantIdentifierPtr];
maxIntegerId.type ← integerId;
maxIntegerId.class ← Z.NEW[IdentifierTail←[constant[
scalarLink: NIL, value: LAST[PascalInteger]]]];
trueId ← NARROW[NewIdent[name: "TRUE"], ConstantIdentifierPtr];
trueId.type ← booleanId;
trueId.class ← Z.NEW[IdentifierTail←[constant[scalarLink: NIL, value: 1]]];
falseId ← NARROW[NewIdent[name: "FALSE"], ConstantIdentifierPtr];
falseId.type ← booleanId;
falseId.class ← Z.NEW[IdentifierTail←[constant[scalarLink: trueId, value: 0]]];
boolean.firstId ← falseId;
nilId ← NARROW[NewIdent[name: "NIL"], ConstantIdentifierPtr];
nilId.type ← nil; -- I guess...
nilId.class ← Z.NEW[IdentifierTail←[constant[scalarLink: NIL, value: 0]]];
FOR s IN StandardFiles DO
id: IdentifierPtr ← NewIdent[name: PascalStandardFileNames[s]];
id.type ← textFile;
id.class ← Z.NEW[IdentifierTail←[variable[]]];
ENDLOOP;
FOR s IN StandardProcedures DO
id: IdentifierPtr ← NewIdent[name: PascalStandardProcedureNames[s]];
id.type ← nilGeneralTypePtr;
id.class ← Z.NEW[IdentifierTail←[procedure[source: standard[s]]]];
ENDLOOP;
FOR s IN StandardFunctions DO
id: IdentifierPtr ← NewIdent[name: PascalStandardFunctionNames[s]];
id.type ← integer;
the function actually tells its own type
id.class ← Z.NEW[IdentifierTail←[procedure[source: standard[s]]]];
ENDLOOP;
END; -- of InitializeStandards
InitializeModules: PUBLIC PROCEDURE =
BEGIN
MB: PROCEDURE [sy: Symbol] = {MustBe[sy, "", MalformedInstr]};
GetFileNameFromSource: PROCEDURE [ext: ROPE] RETURNS [ROPE] =
BEGIN
fileName: ROPE;
IF sy = identSy THEN
BEGIN
fileName←RopeSayIdent[];
InSymbol[];
IF CouldBe[periodSy, ""] AND sy = identSy THEN
BEGIN
fileName ← Rope.Cat[fileName, ".", ident];
InSymbol[];
END
ELSE fileName ← Rope.Cat[fileName, ext];
END
ELSE Error[MalformedInstr];
RETURN[fileName];
END; -- of GetFileNameFromSource
NewFileQ: PROCEDURE [ext: ROPE] RETURNS [OutputQueuePtr] = {
RETURN[Z.NEW[OutputQueue←
[contents: "",
fileName: GetFileNameFromSource[ext]]]]};
ReadDestination: PROCEDURE RETURNS [dest: DestinationPtr] = {
read a defsModule, implModule pair from the input stream, and return
the corresponding Destination record
defs, impl: IdentifierPtr;
defsTail: REF defsModule IdentifierTail;
implTail: REF implModule IdentifierTail;
markAsExportee: BOOL;
IF sy # identSy THEN Error[MalformedInstr];
defs ← IdentLookup[pset: defsModules];
defsTail ← NARROW[defs.class];
markAsExportee ← defsTail.exportMe;
InSymbol[];
IF sy = mulOpSy AND op = mulOp THEN {markAsExportee ← FALSE; InSymbol[]};
MB[commaSy];
impl ← IdentLookup[pset: implModules];
InSymbol[];
implTail ← NARROW[impl.class];
IF markAsExportee AND
IdentLookup[name: defs.name, pset: implTail.exportees, couldFail: TRUE] = NIL
THEN InsertOldIdent[id: defs, pset: implTail.exportees];
dest ← Z.NEW[Destination ← [defsModule: defs, implModule: impl]];
RETURN[dest];
};
DeclareDefs: PROCEDURE = { -- process the declaration of a defs module in the mod file
defs: IdentifierPtr;
defsTail: REF defsModule IdentifierTail;
exportFromConfig: BOOLEANFALSE;
InSymbol[]; -- throw away the word "definitions"
IF sy # identSy THEN Error[MalformedInstr];
defs ← NewIdent[pset: defsModules];
defsTail ← Z.NEW[defsModule IdentifierTail ← [defsModule[q: NewFileQ[".mesa"]]]];
defs.class ← defsTail;
defsTail.openees ← CreateIdentifierSet[];
defsTail.importees ← CreateIdentifierSet[];
IF sy = mulOpSy AND op = mulOp THEN { -- exported interface
InSymbol[];
exportFromConfig ← TRUE;
};
IF CouldBe[lParentSy] THEN {
ReadOpenee: PROC = {
openee: IdentifierPtr;
IF sy # identSy THEN Error[MalformedInstr];
openee ← IdentLookup[pset: defsModules, couldFail: TRUE];
IF openee = NIL THEN openee ← IdentLookup[pset: configImports];
InsertOldIdent[id: openee, pset: defsTail.openees];
InSymbol[];
IF sy = mulOpSy AND op = mulOp THEN InSymbol[]
ELSE InsertOldIdent[id: openee, pset: defsTail.importees];
};
SequenceOf[ReadOpenee, commaSy];
MB[rParentSy];
};
MB[semiColonSy];
SELECT sy FROM
externSy => {
defsTail.compileMe ← FALSE;
defsTail.q.fileName ← "";
};
forwardSy => NULL;
identSy => {
IF NOT Rope.Equal[ident, "TRASH"] THEN Error[MalformedInstr];
defsTail.compileMe ← defsTail.exportMe ← FALSE;
defsTail.q.fileName ← "";
};
ENDCASE => Error[MalformedInstr];
IF exportFromConfig THEN {
IF sy = identSy THEN Error[ImproperType];
[] ← NewIdent[name: defs.name, pset: configExports];
};
InSymbol[];
MB[semiColonSy];
};
DeclareImpl: PROCEDURE = {
process the declaration of an impl module in the mod file
impl: IdentifierPtr;
implTail: REF implModule IdentifierTail;
InSymbol[]; -- throw away the word "program"
IF sy # identSy THEN Error[MalformedInstr];
impl ← NewIdent[pset: implModules];
implTail ← Z.NEW[implModule IdentifierTail ← [implModule[q: NewFileQ[".mesa"]]]];
impl.class ← implTail;
implTail.openedDefs ← CreateIdentifierSet[];
implTail.importedDefs ← CreateIdentifierSet[];
implTail.openedAndImportedImpls ← CreateIdentifierSet[];
implTail.exportees ← CreateIdentifierSet[];
IF CouldBe[lParentSy] THEN
{ReadOpenee: PROC =
{openee: IdentifierPtr;
IF sy # identSy THEN Error[MalformedInstr];
openee ← IdentLookup[pset: defsModules, couldFail: TRUE];
IF openee = NIL THEN openee ← IdentLookup[pset: configImports, couldFail: TRUE];
IF openee = NIL THEN
{ -- special case of importing a program module via pointer to frame
openee ← IdentLookup[pset: implModules];
InsertOldIdent[id: openee, pset: implTail.openedAndImportedImpls];
InSymbol[]}
ELSE
{InSymbol[];
InsertOldIdent[id: openee, pset: implTail.openedDefs];
IF sy = mulOpSy AND op = mulOp THEN InSymbol[]
ELSE InsertOldIdent[id: openee, pset: implTail.importedDefs]};
};
SequenceOf[ReadOpenee, commaSy];
MB[rParentSy]};
MB[semiColonSy];
SELECT sy FROM
externSy => {implTail.compileMe ← FALSE; implTail.q.fileName ← ""};
forwardSy => NULL;
identSy => {IF NOT Rope.Equal[ident, "TRASH"] THEN Error[MalformedInstr];
implTail.compileMe ← implTail.bindMe ← FALSE;
implTail.q.fileName ← ""};
ENDCASE => Error[MalformedInstr];
InSymbol[];
MB[semiColonSy]};
ModuleDefine: PROCEDURE[] =
BEGIN
dest: DestinationPtr;
ParseOuterItem: PROCEDURE[] =
BEGIN
IF sy # identSy THEN Error[MalformedInstr];
SELECT TRUE FROM
Rope.Equal[ident, "$OTHER←PROCS$"] => defaultDest[proc] ← dest;
Rope.Equal[ident, "$OTHER←TYPES$"] => defaultDest[type] ← dest;
Rope.Equal[ident, "$OTHER𡤌ONSTS$"] => defaultDest[const] ← dest;
Rope.Equal[ident, "$OTHER←VARS$"] => defaultDest[var] ← dest;
Rope.Equal[ident, "$GLOBAL←LABELS$"] => defaultDest[globalLabel] ← dest;
Rope.Equal[ident, "$MAIN$"] => defaultDest[main] ← dest;
Rope.Equal[ident, "$REST$"] =>
FOR t: ItemType IN ItemType DO
IF defaultDest[t] = NIL THEN defaultDest[t] ← dest ENDLOOP;
ENDCASE =>
BEGIN
m: IdentifierPtr ← NewIdent[pset: configTail.mentionedIdents];
m.type ← nilGeneralTypePtr;
m.class ← Z.NEW[IdentifierTail←[outerItem[dest: dest]]];
END;
InSymbol[];
END; -- of ParseModuleSon;
dest ← ReadDestination[];
MB[becomesSy];
IF sy # semiColonSy THEN
SequenceOf[ParseOuterItem, commaSy, ""];
END; -- of ModuleDefine
SayTimeComment: PROCEDURE =
BEGIN
time: ROPE;
time ← IO.PutFR["-- Pascal-to-Mesa translator output, translated at %g",IO.time[]];
SayLine[time];
SayLine[];
END; -- of SayTimeComment
SayFileNameComment: PROCEDURE [r: ROPE] =
BEGIN
comment: ROPE;
comment ← IO.PutFR["-- file: %g",IO.rope[r]];
SayLine[comment];
END; -- of SayFileNameComment
GenerateModuleBoilerPlate: PROCEDURE [id: IdentifierPtr] =
BEGIN
q: OutputQueuePtr;
moduleKind: {defs, impl};
defsTail: REF defsModule IdentifierTail;
implTail: REF implModule IdentifierTail;
first: BOOLEAN;
SayDirLine: PROCEDURE [id: IdentifierPtr] =
BEGIN
IF first THEN first ← FALSE ELSE {SayLine[","]; Say[" "]};
SayIdent[id.name];
IF targetLanguage # cedar THEN
{ Say[": FROM """]; SayIdent[id.name]; Say[""""]};
END;
SayModule: PROCEDURE [id: IdentifierPtr] =
BEGIN
IF first THEN first ← FALSE ELSE Say[", "];
SayIdent[id.name];
END;
WITH id.class SELECT FROM
thisTail: REF defsModule IdentifierTail =>
{moduleKind ← defs; defsTail ← thisTail; q ← thisTail.q};
thisTail: REF implModule IdentifierTail =>
{moduleKind ← impl; implTail ← thisTail; q ← thisTail.q};
ENDCASE => ERROR;
PushOut[q];
SayFileNameComment[q.fileName];
SayTimeComment[];
SayLine[];
SayLine["DIRECTORY"];
Say[" "];
first ← TRUE;
SELECT moduleKind FROM
defs => EnumerateIdentifierSet[pset: defsTail.openees, p: SayDirLine]; -- only the asked for
impl => {EnumerateIdentifierSet[pset: implTail.openedDefs, p: SayDirLine];
EnumerateIdentifierSet[pset: implTail.openedAndImportedImpls, p: SayDirLine]};
and imported programs too, sad to say
ENDCASE => ERROR;
SayLine[";"];
SayLine[];
SayIdent[id.name];
SELECT moduleKind FROM
defs => Say[": DEFINITIONS"];
impl => Say[": PROGRAM"];
ENDCASE => ERROR;
Say[" IMPORTS "];
first ← TRUE;
SELECT moduleKind FROM
defs => {EnumerateIdentifierSet[pset: defsTail.importees, p: SayModule]; SayLine[" ="]};
impl => {
EnumerateIdentifierSet[pset: implTail.importedDefs, p: SayModule];
EnumerateIdentifierSet[pset: implTail.openedAndImportedImpls, p: SayModule];
Say[" EXPORTS "];
first ← TRUE;
EnumerateIdentifierSet[pset: implTail.exportees, p: SayModule];
SayLine[" = PUBLIC"];
};
ENDCASE => ERROR;
Say["BEGIN OPEN "];
first ← TRUE;
SELECT moduleKind FROM
defs => EnumerateIdentifierSet[pset: defsTail.openees, p: SayModule];
impl => {EnumerateIdentifierSet[pset: implTail.openedDefs, p: SayModule];
EnumerateIdentifierSet[pset: implTail.openedAndImportedImpls, p: SayModule]};
ENDCASE => ERROR;
SayLine[";"];
q ← CopyAndPopOut[];
SELECT moduleKind FROM
defs => defsTail.q ← q;
impl => implTail.q ← q;
ENDCASE => ERROR;
END; -- of GenerateModuleBoilerPlate
ParseCompileDifferently: PROCEDURE [method: REF ANY] =
BEGIN
id: IdentifierPtr;
curSeg: SegmentIdentifierTailPtr ← segmentsTail;
name: Name ← ident;
cid: REF compileDifferently IdentifierTail;
MB[identSy];
WHILE CouldBe[periodSy, ""] DO
id ← IdentLookup[
name: name, pset: curSeg.mentionedProcedures, couldFail: TRUE];
IF id = NIL THEN
BEGIN
id ← NewIdent[name: name, pset: curSeg.mentionedProcedures];
id.class ← Z.NEW[programSegment IdentifierTail ←
[programSegment[mentionedVariables: CreateIdentifierSet[],
mentionedProcedures: CreateIdentifierSet[]]]];
END;
WITH id.class SELECT FROM
sid: REF programSegment IdentifierTail => curSeg ← sid; ENDCASE;
name ← ident;
MB[identSy];
ENDLOOP;
id ← IdentLookup[
name: name, pset: curSeg.mentionedVariables, couldFail: TRUE];
IF id = NIL THEN
BEGIN
id ← NewIdent[name: name, pset: curSeg.mentionedVariables];
cid ← Z.NEW[compileDifferently IdentifierTail ←[compileDifferently[]]];
id.class ← cid;
END
ELSE cid ← NARROW[id.class];
WITH method SELECT FROM
arrayMethod: REF ArrayDifferentlyMethod => cid.arrayHow ← arrayMethod^;
procMethod: REF ProcDifferentlyMethod => cid.procHow ← procMethod^;
ENDCASE;
END; -- of ParseCompileDifferently
ParseSpecialArray: PROCEDURE = {ParseCompileDifferently[
NEW[ArrayDifferentlyMethod ← specialArray]]};
ParseProcArray: PROCEDURE = {ParseCompileDifferently[
NEW[ArrayDifferentlyMethod ← procArray]]};
ParseComputedSeqArray: PROCEDURE = {ParseCompileDifferently[
NEW[ArrayDifferentlyMethod ← computedSeqArray]]};
ParseInlineProc: PROCEDURE = {ParseCompileDifferently[
NEW[ProcDifferentlyMethod ← inlineProc]]};
instrStream: STREAM;
instrName: ROPE;
PushOut[]; -- throw away the translated output until we really start!
SourceFromStream[IO.RIS[commandHandle.commandLine], "commandLine"];
InSymbol[];
instrName ← GetFileNameFromSource[ext: ".mod"];
instrStream ← FS.StreamOpen[instrName];
SourceFromStream[instrStream, instrName];
InSymbol[];
defsModules ← CreateIdentifierSet[];
implModules ← CreateIdentifierSet[];
configImports ← CreateIdentifierSet[];
configExports ← CreateIdentifierSet[];
segmentsTail ← Z.NEW[programSegment IdentifierTail];
segmentsTail.mentionedProcedures ← CreateIdentifierSet[];
segmentsTail.mentionedVariables ← CreateIdentifierSet[];
segments ← Z.NEW[Identifier← [hash: 0]]; -- a nil hash is OK since we never search for it
segments.class ← segmentsTail;
configTail ← Z.NEW[config IdentifierTail];
configTail.mentionedIdents ← CreateIdentifierSet[];
config ← Z.NEW[Identifier← [hash: 0]];
config.class ← configTail;
FOR t: ItemType IN ItemType DO defaultDest[t] ← NIL ENDLOOP;
readySourceFileSeq ← NIL;
IF CouldBe[lParentSy, ""] THEN
BEGIN -- we should modularize the program
AddSourceFile: PROCEDURE =
BEGIN
IF sy=identSy THEN
BEGIN
p: SourceFileSeqPtr ← readySourceFileSeq;
IF p=NIL THEN readySourceFileSeq ← Z.NEW[SourceFileSeq←
[next: NIL, name: GetFileNameFromSource[".pas"]]]
ELSE
BEGIN
WHILE p.next#NIL DO p ← p.next ENDLOOP;
p.next ← Z.NEW[SourceFileSeq←
[next: NIL, name: GetFileNameFromSource[".pas"]]];
END
END
ELSE Error[MalformedIdList];
END;
IF NOT Rope.Equal[ident, "CONFIGURATION"] THEN Error[MalformedInstr];
InSymbol[];
configName ← ident;
configQ ← NewFileQ[".config"];
IF CouldBe[lParentSy] THEN {
ReadConfigImportee: PROC = {
IF sy # identSy THEN Error[MalformedInstr];
[] ← NewIdent[pset: configImports];
InSymbol[]
};
SequenceOf[ReadConfigImportee, commaSy];
MB[rParentSy]
};
MB[semiColonSy];
modularize ← TRUE;
DO
SELECT sy FROM
beginSy => EXIT;
programSy => DeclareImpl[];
identSy => {IF NOT Rope.Equal[ident, "DEFINITIONS"] THEN Error[MalformedInstr];
DeclareDefs[]};
ENDCASE => Error[MalformedInstr];
ENDLOOP;
MB[beginSy];
SequenceOf[ModuleDefine, semiColonSy, ""];
[] ← CouldBe[semiColonSy, ""];
MB[endSy];
MB[rParentSy];
MB[becomesSy];
SequenceOf[AddSourceFile, commaSy];
END
ELSE
BEGIN -- we shouldn't modularize the program
moduleId: IdentifierPtr;
fileName: Name;
ERROR; -- SIMPLE CASE NOT CURRENTLY IMPLEMENTED
modularize ← notAtAll;
IF sy # identSy THEN Error[MalformedInstr];
moduleId ← NewIdent[pset: modules];
fileName ← Rope.Cat[RopeSayIdent[ident], ".mesa"];
configName ← ident;
readySourceFileSeq ← Z.NEW[SourceFileSeq ← [next: NIL, name: GetFileNameFromSource[".pas"]]];
mainQPtr ← Z.NEW[OutputQueue ← [contents: "", fileName: fileName]];
moduleId.class ← Z.NEW[IdentifierTail ← [moduleName[q: mainQPtr, f: impl]]];
mainId ← moduleId;
END;
[] ← CouldBe[semiColonSy, ""];
IF Rope.Equal[ident, "CAPITALIZE"] AND CouldBe[identSy, ""] THEN
BEGIN
SELECT TRUE FROM
Rope.Equal[ident, "CHARS"] AND CouldBe[identSy, ""] =>
capitalizeChars ← TRUE;
ENDCASE => {capitalizeChars ← TRUE; capitalizeStrings ← TRUE};
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "COMPILERSWITCHES"] AND CouldBe[identSy, ""] THEN
BEGIN
MB[stringConstSy];
compilerSwitches ← ident;
[] ← CouldBe[semiColonSy, ""];
END ELSE compilerSwitches ← NIL;
IF Rope.Equal[ident, "COMPUTEDSEQARRAY"] AND CouldBe[identSy, ""] THEN
BEGIN
SequenceOf[ParseComputedSeqArray, commaSy, ""];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "INLINE"] AND CouldBe[identSy, ""] THEN
BEGIN
SequenceOf[ParseInlineProc, commaSy, ""];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "INVENTFILENAMES"] AND CouldBe[identSy, ""] THEN
BEGIN
IF Rope.Equal[ident, "TRUE"] AND CouldBe[identSy, ""] THEN
useVarNamesForFileNames ← TRUE
ELSE IF Rope.Equal[ident, "FALSE"] AND CouldBe[identSy, ""] THEN
useVarNamesForFileNames ← FALSE
ELSE Error[MalformedInstr];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "MAKEFILE"] AND CouldBe[identSy, ""] THEN
BEGIN
makeFileQ ← NewFileQ[".cm"];
InSymbol[];
END;
IF Rope.Equal[ident, "NAMED"] AND CouldBe[identSy, ""] THEN
BEGIN
[] ← CouldBe[identSy, ""]; -- parameters
paramsHaveNames ← TRUE;
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "PREDEFINE"] AND CouldBe[identSy, ""] THEN
BEGIN
TranslateBlock[inner];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "PROCARRAY"] AND CouldBe[identSy, ""] THEN
BEGIN
SequenceOf[ParseProcArray, commaSy, ""];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "SPECIAL"] AND CouldBe[identSy, ""] THEN
BEGIN
[] ← CouldBe[arraySy, ""];
SequenceOf[ParseSpecialArray, commaSy, ""];
[] ← CouldBe[semiColonSy, ""];
END;
IF Rope.Equal[ident, "TARGET"] AND CouldBe[identSy, ""] THEN
BEGIN
SELECT TRUE FROM
Rope.Equal[ident, "MESA"] AND CouldBe[identSy, ""] =>
{ targetLanguage ← mesa;
PascalIntegerName ← "INTEGER";
pointerName ← "POINTER TO ";
varPointerName ← "POINTER TO "};
Rope.Equal[ident, "LONG"] AND CouldBe[identSy, ""] =>
{ [] ← CouldBe[identSy, ""]; --throw away MESA
targetLanguage ← longMesa;
PascalIntegerName ← "INTEGER";
pointerName ← "LONG POINTER TO ";
varPointerName ← "LONG POINTER TO "};
ENDCASE =>
{ [] ← CouldBe[identSy, ""]; --throw away CEDAR
targetLanguage ← cedar;
PascalIntegerName ← "INT";
pointerName ← "LONG POINTER TO ";
varPointerName ← "LONG POINTER TO "};
[] ← CouldBe[semiColonSy, ""];
END;
sourceFileSeq ← readySourceFileSeq;
SourceFromNextStream[];
PopOut[];
IF modularize THEN
BEGIN
first: BOOLEANTRUE;
SayDefsModule: PROCEDURE [id: IdentifierPtr] =
BEGIN
IF first THEN first ← FALSE ELSE Say[", "];
SayIdent[id.name];
END; -- of SayDefsModule
SayImplModule: PROCEDURE [id: IdentifierPtr] =
BEGIN
implTail: REF implModule IdentifierTail ← NARROW[id.class];
IF implTail.bindMe THEN
{IF first THEN first ← FALSE ELSE Say[", "];
SayIdent[id.name]};
END; -- of SayImplModule
SayCodeModule: PROCEDURE [id: IdentifierPtr] =
BEGIN
implTail: REF implModule IdentifierTail ← NARROW[id.class];
IF implTail.bindMe THEN
{IF first THEN first ← FALSE ELSE Say["; "];
SayIdent[id.name]};
END; -- of SayCodeModule
PushOut[configQ];
SayFileNameComment[configQ.fileName];
SayLine["-- Pascal-to-Mesa Configuration"];
SayLine[""];
SayTimeComment[];
SayIdent[configName];
Say[": CONFIGURATION IMPORTS "];
first ← TRUE;
EnumerateIdentifierSet[pset: configImports, p: SayDefsModule];
SayLine[""];
IF NOT EmptyIdentifierSet[configExports] THEN {
Say["EXPORTS "];
first ← TRUE;
EnumerateIdentifierSet[pset: configExports, p: SayDefsModule];
SayLine[""];
};
Say["CONTROL "];
first ← TRUE;
EnumerateIdentifierSet[pset: implModules, p: SayImplModule];
SayLine[" ="];
SayLine["BEGIN"];
first ← TRUE;
EnumerateIdentifierSet[pset: implModules, p: SayCodeModule];
SayLine[""];
SayLine["END."];
PopOut[]; -- doesn't delete the file, merely closes it
IF makeFileQ # NIL THEN
BEGIN
SayADefs: PROC [id: IdentifierPtr] =
{defsTail: REF defsModule IdentifierTail = NARROW[id.class];
IF defsTail.compileMe THEN {Say[" "]; SayIdent[id.name]}};
SayAnImpl: PROC [id: IdentifierPtr] =
{implTail: REF implModule IdentifierTail = NARROW[id.class];
IF implTail.compileMe THEN {Say[" "]; SayIdent[id.name]}};
PushOut[makeFileQ];
Say["Compile"];
IF Rope.Length[compilerSwitches]#0 THEN {Say[" "]; Say[compilerSwitches]};
EnumerateIdentifierSet[pset: defsModules, p: SayADefs];
EnumerateIdentifierSet[pset: implModules, p: SayAnImpl];
Say["; Bind "];
SayIdent[configName];
SayCh['\n];
PopOut[];
END;
END;
EnumerateIdentifierSet[defsModules, GenerateModuleBoilerPlate];
EnumerateIdentifierSet[implModules, GenerateModuleBoilerPlate];
PushOut[];
SayIdent[configName];
SayLine["Run: UnsafeCommandProc = BEGIN "];
initCodeQPtr ← CopyAndPopOut[];
END; -- of InitializeModules
FinishModules: PUBLIC PROCEDURE =
BEGIN
CloseOutputFile: PROCEDURE [id: IdentifierPtr] =
BEGIN
WITH id.class SELECT FROM
implTail: REF implModule IdentifierTail =>
BEGIN
PushOut[implTail.q];
IF id = defaultDest[main].implModule THEN
BEGIN
SayLine[" END;"];
SayLine[""];
Say["PascalRegister["""];
SayIdent[configName];
Say[""", "];
SayIdent[configName];
SayLine["Run];"];
END;
SayLine[""];
SayLine["END."];
PopOut[]; -- closes the file
END;
defsTail: REF defsModule IdentifierTail =>
BEGIN
PushOut[defsTail.q];
SayLine[""];
SayLine["END."];
PopOut[]; -- closes the file
END;
ENDCASE;
END; -- of CloseOutputFile
WHILE outLevel > 0 DO PopOut[] ENDLOOP; -- close any files
EnumerateIdentifierSet[defsModules, CloseOutputFile];
DisposeIdentifierSet[defsModules];
EnumerateIdentifierSet[implModules, CloseOutputFile];
DisposeIdentifierSet[implModules];
DisposeIdentifierSet[configTail.mentionedIdents];
DisposeIdentifierSet[segmentsTail.mentionedProcedures];
DisposeIdentifierSet[segmentsTail.mentionedVariables];
FOR t: ItemType IN ItemType DO defaultDest[t] ← NIL ENDLOOP;
END; -- of FinishModules
END. -- of PasInit --