C2CMainImpl.mesa
Copyright Ó 1987, 1988, 1989, 1990, 1991, 1992, 1993 by Xerox Corporation. All rights reserved.
Christian Jacobi, 1987
Christian Jacobi, January 25, 1993 7:14 pm PST
Russ Atkinson (RRA) January 14, 1988 6:15:51 pm PST
JKF May 25, 1990 9:25:06 am PDT
Willie-s, September 24, 1991 6:12 pm PDT
Michael Plass, September 27, 1991 1:46 pm PDT
DIRECTORY
BasicTime,
C2CAccess,
C2CAddressing,
C2CAddressingOps,
C2CBasics,
C2CDefs,
C2CEmit,
C2CEnables,
C2CCodeUtils,
C2CIntCodeUtils,
C2CPreprocessing,
C2CMain,
C2CMode,
C2CGlobalFrame,
C2CNames,
C2CRunTime,
C2CStateUtils,
C2CSourcePositions,
C2CTarget,
C2CTypes,
Convert,
IntCodeDefs,
IntCodeStuff,
IntCodeUtils,
IO,
Process,
RefText,
Rope,
SymTab;
C2CMainImpl: CEDAR PROGRAM
IMPORTS BasicTime, C2CAccess, C2CAddressingOps, C2CBasics, C2CEmit, C2CCodeUtils, C2CEnables, C2CGlobalFrame, C2CIntCodeUtils, C2CNames, C2CMain, C2CMode, C2CPreprocessing, C2CRunTime, C2CSourcePositions, C2CStateUtils, C2CTarget, C2CTypes, Convert, IntCodeUtils, IntCodeStuff, IO, Process, RefText, Rope, SymTab
EXPORTS C2CMain =
BEGIN
OPEN IntCodeDefs, C2CBasics, C2CDefs, C2CMain, C2CMode;
ROPE: TYPE = Rope.ROPE;
declMode: Mode ~ SetExpr[NIL, TRUE];
skipMode: Mode ~ DSetBaseSize[SetAModeNC[Like[rhs: TRUE, stat: TRUE], skip], 0];
stringPieceMaxLength: INT = C2CTarget.RoundUpCharsToWords[200];
myKeyForFirstProc: REF INT ¬ NEW[INT]; --unique
myKeyForModuleEncountered: REF INT ¬ NEW[INT]; --unique
myKeyForFormalReturn: REF INT ¬ NEW[INT]; --unique
myKeyForReturnBits: REF INT ¬ NEW[INT]; --unique
Cat2: PROC [c1, c2: Code] RETURNS [c: Code] = {
IF c2=NIL THEN RETURN [c1];
IF c1=NIL THEN RETURN [c2];
RETURN [C2CEmit.Cat[c1, c2]]
};
GenNodeList: PROC [nodeList: IntCodeDefs.NodeList, mode: Mode, outsideTemporaryDecl: BOOL ¬ FALSE, mayOmmitLastEnablePop: BOOL ¬ FALSE] RETURNS [cc: CodeCont] = {
--"statement" nodes
--outsideTemporaryDecl: Set FALSE in doubt
count: INT ¬ 0;
rqMode: Mode ¬ mode;
useMode: Mode;
skipMode: Mode ¬ SetAMode[mode, skip];
saveDeclC: Code ¬ NIL;
lastNode, needComma, makesRealCode, adressable, makeTemporaryDecl: BOOL ¬ FALSE;
FOR nodes: IntCodeDefs.NodeList ¬ nodeList, nodes.rest WHILE nodes#NIL DO
wasDead: BOOL ¬ FALSE;
cc1: CodeCont;
useMode ¬ skipMode;
lastNode ¬ FALSE;
IF cc.sc#NIL THEN wasDead ¬ C2CEmit.GetIsDead[cc.sc];
IF wasDead AND ~C2CIntCodeUtils.HasLabel[nodes.first] THEN {
cc.sc ¬ C2CEmit.CatRemark[cc.sc, "c2c skipped dead code"];
cc.sc ¬ C2CEmit.Cat[cc.sc, C2CEmit.line]; count ¬ 0;
C2CEmit.SetDead[cc.sc];
LOOP
};
makesRealCode ¬ C2CIntCodeUtils.NodeHasCode[nodes.first];
IF makesRealCode THEN
IF ~C2CIntCodeUtils.AnyNodeHasCode[nodes.rest] THEN {
useMode ¬ rqMode;
lastNode ¬ TRUE;
};
makeTemporaryDecl ¬ GetAMode[useMode]=skip;
IF makeTemporaryDecl AND outsideTemporaryDecl AND nodeList.rest=NIL THEN
makeTemporaryDecl ¬ FALSE;
IF makesRealCode AND makeTemporaryDecl THEN {
saveDeclC ¬ C2CEmit.CollectCode[temporaryDeclarations];
};
IF mayOmmitLastEnablePop AND nodes.rest=NIL AND nodes.first#NIL AND ISTYPE[nodes.first, EnableNode]
THEN cc1 ¬ GenEnableNode[enableNode: NARROW[nodes.first], mode: useMode, skipPost: TRUE]
ELSE cc1 ¬ GenNode[node: nodes.first, mode: useMode];
IF makesRealCode AND makeTemporaryDecl THEN {
declC: Code ¬ C2CEmit.CollectCode[temporaryDeclarations];
IF declC#NIL THEN {
dead: BOOL ¬ C2CEmit.GetIsDead[cc1.sc];
cc1.sc ¬ C2CEmit.Cat[enterBlock, declC, cc1.sc, exitBlock];
IF dead THEN C2CEmit.SetDead[cc1.sc];
};
IF saveDeclC#NIL THEN
C2CEmit.AppendCode[temporaryDeclarations, saveDeclC];
};
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF (count¬count+1) > 5 AND cc1.sc#NIL AND nodes.rest#NIL THEN {
dead: BOOL ¬ C2CEmit.GetIsDead[cc.sc];
cc.sc ¬ C2CEmit.Cat[cc.sc, C2CEmit.line]; count ¬ 0;
IF dead THEN C2CEmit.SetDead[cc.sc];
};
IF cc1.ec#NIL THEN {
IF ~makesRealCode THEN {
cc.sc ¬ C2CEmit.Cat[cc.sc, cc1.ec, ";\n"];
IF wasDead THEN C2CEmit.SetDead[cc.sc];
}
ELSE IF ~lastNode OR GetAMode[rqMode]=skip THEN
cc.sc ¬ C2CEmit.Cat[cc.sc, "(void) ", cc1.ec, ";\n"]
ELSE {
IF count>5 THEN {count ¬ 0; cc1.ec ¬ C2CEmit.Cat[cc1.ec, C2CEmit.line]};
cc.ec ¬ cc1.ec;
}
};
ENDLOOP;
FreeMode[skipMode];
};
GenNode: PUBLIC PROC [node: Node, mode: Mode] RETURNS [cc: CodeCont] = {
Process.CheckForAbort[];
IF node = nullNode THEN {
RETURN
};
WITH node SELECT FROM
varNode: Var => {
cc ¬ GenVarNode[varNode: varNode, mode: mode];
};
constNode: ConstNode => {
cc ¬ GenConstNode[constNode: constNode, mode: mode];
};
blockNode: BlockNode => {
cc ¬ GenBlockNode[blockNode: blockNode, mode: mode];
};
declNode: DeclNode => {
cc.sc ¬ GenDeclNode[declNode: declNode, mode: mode];
};
enableNode: EnableNode => {
cc ¬ GenEnableNode[enableNode: enableNode, mode: mode];
};
assignNode: AssignNode => {
cc ¬ GenAssignNode[assignNode: assignNode, mode: mode];
};
condNode: CondNode => {
cc ¬ GenCondNode[condNode: condNode, mode: mode];
};
labelNode: LabelNode => {
cc ¬ GenLabelNode[labelNode: labelNode, mode: mode];
};
gotoNode: GotoNode => {
cc.sc ¬ GenGotoNode[gotoNode: gotoNode, mode: mode];
};
applyNode: ApplyNode => {
cc ¬ GenApplyNode[applyNode: applyNode, mode: mode];
};
lambdaNode: LambdaNode => {
cc.sc ¬ GenLambdaNode[lambdaNode: lambdaNode, mode: mode];
};
returnNode: ReturnNode => {
cc ¬ GenReturnNode[returnNode: returnNode, mode: mode];
};
operNode: OperNode => {
cc ¬ GenNakedOperNode[operNode: operNode, mode: mode];
};
machineCodeNode: MachineCodeNode => {
CantHappenCedar; --only allowed in context of applyNode
};
moduleNode: ModuleNode => {
GenModuleNode[moduleNode: moduleNode, mode: mode];
};
sourceNode: SourceNode => {
cc ¬ GenSourceNode[sourceNode: sourceNode, mode: mode];
};
commentNode: CommentNode => {
cc.sc ¬ GenCommentNode[commentNode: commentNode, mode: mode];
};
ENDCASE => CaseMissing;
};
AssBitAddrOfId: PROC [name: ROPE, mode: Mode, bitOffset: INT ¬ 0] RETURNS [sc: Code] = {
--given an identifier, returns statement-code assigning the bit address into a template
--bitOffset bits from left
ac: C2CAddressing.AddressContainer ¬ GetAddrContainer[mode];
IF ~GetAMode[mode]=assBitAddr THEN CantHappen;
sc ¬ C2CEmit.Cat[
C2CEmit.Cat[ac.words, " = (word) &", name, "; "],
C2CEmit.Cat[ac.bits, " = ", C2CCodeUtils.ConstI[bitOffset], ";\n"]
];
};
AssAddrOfId: PROC [r: ROPE, mode: Mode] RETURNS [sc: Code] = {
--given an identifier, returns statement-code assigning the address into a template
--assumes precedence high enough
template: ROPE ¬ GetTemplate[mode];
IF ~GetAMode[mode]=assAddr THEN CantHappen;
sc ¬ C2CEmit.Cat[template, " = &", r, ";\n"];
};
ConstVal: PROC [w: Word] RETURNS [ROPE] = {
i: INT ¬ IntCodeUtils.WordToInt[w];
IF i<0 AND i>-2001
THEN RETURN [ IO.PutFR1[" (word) %g", IO.int[i]] ]
ELSE RETURN [ Convert.RopeFromCard[IntCodeUtils.WordToCard[w]] ];
};
globalSmallConstantsTable: IntCodeUtils.IdTab;
ResetGlobalSmallConstantsTable: PROC [] = {
globalSmallConstantsTable ¬ IntCodeUtils.NewIdTab[]
};
DeclareWordConstant: PROC [w: Word] RETURNS [name: ROPE] = {
--declares an word constant and returns its name
--right adjusted in word
table: IntCodeUtils.IdTab ~ globalSmallConstantsTable;
WITH IntCodeUtils.Fetch[table, IntCodeUtils.WordToInt[w]] SELECT FROM
r: ROPE => name ¬ r;
ENDCASE => {
c: Code;
name ¬ C2CNames.InternalName["const"];
c ¬ C2CEmit.Cat["static ", C2CTarget.word, " ", name];
c ¬ C2CEmit.Cat[c, " = ", ConstVal[w], ";\n"];
C2CEmit.AppendCode[moduleDeclarations, c];
[] ¬ IntCodeUtils.Store[table, IntCodeUtils.WordToInt[w], name];
};
};
StringTableEntryRec: TYPE = RECORD [
name: ROPE ¬ NIL,  --name of template with string [if template is already generated]
count: INT ¬ 1 --how often this string is used
];
CountUsageOfStrings: PROC [] = {
stringTable: SymTab.Ref ~ SymTab.Create[];
FindConstants: IntCodeUtils.Visitor = {
WITH node SELECT FROM
bytes: BytesConstNode =>
WITH SymTab.Fetch[stringTable, bytes.bytes].val SELECT FROM
entry: REF StringTableEntryRec => entry.count ¬ entry.count+1;
ENDCASE => [] ¬ SymTab.Store[stringTable, bytes.bytes, NEW[StringTableEntryRec]];
ENDCASE => {};
IntCodeUtils.MapNode[node, FindConstants];
RETURN [node];
};
[] ¬ FindConstants[C2CBasics.rootNode];
C2CBasics.PutProp[$stringTable, stringTable]
};
DefineStringCopy: PUBLIC PROC [length: INT, bytes: ROPE] RETURNS [name: ROPE] = {
Generate a constant but only assign the value at run time.
Because C strings do not fullfill eventuel alignment conditions.
type: ROPE ¬ C2CTypes.DefineType[MAX[length*8, C2CTarget.bitsPerWord]];
start: INT ¬ 0;
decl: Code;
name ¬ C2CNames.InternalName["const"];
decl ¬ C2CEmit.Cat["static ", type, " ", name, ";\n"];
C2CEmit.AppendCode[moduleDeclarations, decl];
--split large string into small pieces to prevent blowing up the C compiler
WHILE length>0 DO
chunkSize: INT ¬ MIN[length, stringPieceMaxLength];
dest: ROPE ¬
IF start=0
THEN Rope.Concat["&", name]
ELSE IO.PutFR["( (int) &%g + %g)", IO.rope[name], IO.int[start]];
c: Code ¬ C2CRunTime.MoveBytesDisjoint[
src: C2CEmit.IdentCode[C2CCodeUtils.CString[Rope.Substr[base: bytes, start: start, len: chunkSize]]],
dst: C2CEmit.IdentCode[dest],
nBytes: chunkSize
];
C2CEmit.AppendCode[moduleInitializations, C2CEmit.Cat[c, ";\n"]];
length ¬ length-chunkSize;
start ¬ start+chunkSize;
ENDLOOP;
};
DefineStringStruct: PUBLIC PROC [length: INT, bytes: ROPE] RETURNS [name: ROPE] = {
--for alignments not bigger than single word
First: PROC [] RETURNS [val: CARD ¬ 0] = {
leng: INT ¬ Rope.Length[bytes];
IF ~C2CTarget.consecutiveStringsAllocedAdj THEN NotYetImpl;
IF BITS[CARD]<C2CTarget.bitsPerWord THEN NotYetImpl;
FOR i: INT IN [0..C2CTarget.charsPerWordInString) DO --ENDIAN--
val ¬ val*256;
IF i<leng THEN val ¬ val+ORD[Rope.Fetch[bytes, i]]; --targets collating sequence
ENDLOOP;
};
declaration: ROPE;
first: ROPE ¬ Convert.RopeFromCard[First[]];
rLeng: INT ¬ Rope.Length[bytes];
name ¬ C2CNames.InternalName["string"];
length ¬ C2CTarget.RoundUpCharsToWords[MAX[length, rLeng]];
IF length<=C2CTarget.charsPerWordInString THEN {
declaration ¬ IO.PutFR["static unsigned %g = %g;\n", IO.rope[name], IO.rope[first]];
}
ELSE IF length<=stringPieceMaxLength THEN {
rest: ROPE ¬ C2CCodeUtils.CString[Rope.Substr[bytes, C2CTarget.charsPerWordInString]];
declaration ¬ IO.PutFLR["static struct {unsigned f; char r[%g];} %g = {%g, %g};\n", LIST[ IO.int[length-C2CTarget.charsPerWordInString], IO.rope[name], IO.rope[first], IO.rope[rest]]];
}
ELSE {
pieceNo: INT ¬ 0;
start: INT ¬ C2CTarget.charsPerWordInString;
declaration ¬ "static struct {unsigned f; ";
WHILE start<length DO
pieceLength: INT ¬ MIN[stringPieceMaxLength, length-start];
declaration ¬ IO.PutFR["%g char r%g[%g];", IO.rope[declaration], IO.int[pieceNo], IO.int[pieceLength]];
start ¬ start+pieceLength;
pieceNo ¬ pieceNo+1;
ENDLOOP;
declaration ¬ Rope.Concat[declaration, IO.PutFR["} %g%g= { %g", IO.rope[name], IO.rope[C2CEmit.nestNLine], IO.rope[first]]];
start ¬ C2CTarget.charsPerWordInString;
WHILE start<length DO
pieceLength: INT ¬ MIN[stringPieceMaxLength, length-start];
piece: ROPE ¬ C2CCodeUtils.CString[(IF start<rLeng THEN Rope.Substr[bytes, start, pieceLength] ELSE "")];
declaration ¬ IO.PutFR["%g,\n%g", IO.rope[declaration], IO.rope[piece]];
start ¬ start+stringPieceMaxLength;
ENDLOOP;
declaration ¬ IO.PutFR["%g};%g", IO.rope[declaration], IO.rope[C2CEmit.unNestNLine]];
};
C2CEmit.AppendCode[moduleDeclarations, C2CEmit.Cat[declaration]];
};
GetSymTab: PROC [key: ATOM] RETURNS [SymTab.Ref] = {
WITH C2CBasics.GetProp[key] SELECT FROM
tab: SymTab.Ref => RETURN [tab];
ENDCASE => {
tab: SymTab.Ref ~ SymTab.Create[case: FALSE];
C2CBasics.PutProp[key, tab];
RETURN [tab]
};
};
ConvertSingleRealLiterals: PROC [contents: ByteSequence] RETURNS [ROPE] = {
input parameter has Cedar syntax for floating point literal
return parameter has C syntax for floating point literal
RETURN [contents];
};
ConvertDoubleRealLiterals: PROC [contents: ByteSequence] RETURNS [ROPE] = {
input parameter has Cedar syntax for double precision floating point literal
return parameter has C syntax for double precision floating point literal
RETURN [contents];
};
literalsDirectCast: BOOL ¬ TRUE;
MakeTemplate: PROC [bits: INT, type: ROPE, lit: ROPE] RETURNS [name: ROPE] = {
IF literalsDirectCast
THEN {
name ¬ C2CNames.InternalName["fc"];
C2CEmit.AppendCode[macroDeclarations, "static "];
C2CEmit.AppendCode[macroDeclarations, C2CEmit.Cat[type, name, " = ", lit, ";\n"]];
}
ELSE {
assign: Code;
ptrType: ROPE ¬ C2CTypes.DefinePtrType[bits];
fname: ROPE ¬ C2CNames.InternalName["ff"];
C2CEmit.AppendCode[macroDeclarations, "static "];
C2CEmit.AppendCode[macroDeclarations, C2CEmit.Cat[type, fname, " = ", lit, ";\n"]];
name ¬ C2CStateUtils.DeclareVariable[macroDeclarations, bits, "fc"];
assign ¬ C2CEmit.Cat[" = *(", ptrType, ")&", fname];
C2CEmit.AppendCode[moduleInitializations, C2CEmit.Cat[name, assign, ";\n"]];
};
};
SingleFloatLiteral: PROC [contents: ByteSequence] RETURNS [cc: CodeCont¬[]] = {
template: ROPE;
tab: SymTab.Ref ~ GetSymTab[$SingleRealLiterals];
lit: ROPE ~ ConvertSingleRealLiterals[contents];
WITH SymTab.Fetch[tab, lit].val SELECT FROM
r: ROPE => template ¬ r;
ENDCASE => {
template ¬ MakeTemplate[C2CTarget.bitsPerWord, "float ", lit];
[] ¬ SymTab.Store[tab, lit, template];
};
IF literalsDirectCast
THEN {
cc.ec ¬ C2CEmit.Deref[
c: C2CEmit.IdentCode[Rope.Concat["&", template]],
pointeeBits: C2CTarget.bitsPerWord
]
}
ELSE cc.ec ¬ C2CEmit.IdentCode[template];
};
DoubleFloatLiteral: PROC [contents: ByteSequence] RETURNS [cc: CodeCont¬[]] = {
template: ROPE;
tab: SymTab.Ref ~ GetSymTab[$DRealLiterals];
lit: ROPE ¬ ConvertDoubleRealLiterals[contents];
WITH SymTab.Fetch[tab, lit].val SELECT FROM
r: ROPE => template ¬ r;
ENDCASE => {
template ¬ MakeTemplate[C2CTarget.bitsPerDoubleWord, "double ", lit];
[] ¬ SymTab.Store[tab, lit, template];
};
IF literalsDirectCast
THEN {
cc.ec ¬ C2CEmit.Deref[
c: C2CEmit.IdentCode[Rope.Concat["&", template]],
pointeeBits: C2CTarget.bitsPerDoubleWord
]
}
ELSE cc.ec ¬ C2CEmit.IdentCode[template];
};
GenConstNode: PUBLIC PROC [constNode: ConstNode, mode: Mode] RETURNS [cc: CodeCont] = {
am: C2CAddressing.AddressMode ¬ GetAMode[mode];
IF am=skip THEN CantHappen;
WITH constNode SELECT FROM
wordConst: WordConstNode => {
SELECT am FROM
plain => {cc.ec ¬ C2CEmit.IdentCode[DeclareWordConstant[wordConst.word]]};
value, maskNShift => {
cc.ec ¬ C2CEmit.Cat[ConstVal[wordConst.word]];
cc.ec ¬ C2CEmit.SetPrecedence[cc.ec, primaryPrecedence];
};
assUnits => {
c: Code ¬ C2CEmit.RopeCode[ConstVal[wordConst.word]];
c ¬ C2CEmit.SetPrecedence[c, unaryPrecedence];
cc.sc ¬ C2CAddressingOps.CodeToAssUnits[c, mode];
};
assBitAddr => {
template: ROPE ¬ DeclareWordConstant[wordConst.word];
cc.sc ¬ AssBitAddrOfId[template, mode, C2CTarget.bitsPerWord-constNode.bits];
};
getBitAddr => {
template: ROPE ¬ DeclareWordConstant[wordConst.word];
cc.ec ¬ C2CEmit.TakeAddr[C2CEmit.IdentCode[template]];
IF constNode.bits<C2CTarget.bitsPerWord THEN {
cc.xbc ¬ C2CCodeUtils.ConstC[C2CTarget.bitsPerWord-constNode.bits];
};
};
getAddr, assAddr, skip => CantHappen;
ENDCASE => CaseMissing;
};
bytes: BytesConstNode => {
name: ROPE;
stringTable: SymTab.Ref ~ NARROW[C2CBasics.GetProp[$stringTable]];
entry: REF StringTableEntryRec ~ NARROW[SymTab.Fetch[stringTable, bytes.bytes].val];
length: INT ¬ IF constNode.bits#0
THEN (constNode.bits+7)/8
ELSE Rope.Length[bytes.bytes];
IF entry=NIL THEN CantHappen;
--check whether we already have this string
IF entry.name#NIL THEN name ¬ entry.name
ELSE {
--nice'n easy string literals
IF entry.count<=1 AND bytes.align<=8 AND Rope.Length[bytes.bytes]<=stringPieceMaxLength THEN
SELECT am FROM
plain => {
cc.ec ¬ C2CEmit.IdentCode[C2CCodeUtils.CString[bytes.bytes]];
cc.ec ¬ C2CEmit.SetIsAddress[cc.ec];
RETURN;
};
getAddr => {
cc.ec ¬ C2CEmit.IdentCode[C2CCodeUtils.CString[bytes.bytes]];
RETURN;
};
ENDCASE => {};
--branch independent of actual alignment condition so we can allways reuse template
IF C2CTarget.bitsPerWord<=C2CTarget.bestAlignment AND C2CTarget.consecutiveStringsAllocedAdj
THEN {
name ¬ DefineStringStruct[length, bytes.bytes];
}
ELSE {
name ¬ DefineStringCopy[length, bytes.bytes];
};
entry.name ¬ name;
};
SELECT am FROM
plain, maskNShift, value =>
--addr cast and deref so we get the canonical type
cc.ec ¬ C2CEmit.Deref[C2CEmit.TakeAddr[C2CEmit.IdentCode[name], TRUE], constNode.bits];
getAddr => cc.ec ¬ C2CEmit.TakeAddr[C2CEmit.IdentCode[name], TRUE];
assBitAddr => cc.sc ¬ AssBitAddrOfId[name, mode, 0];
assAddr => cc.sc ¬ AssAddrOfId[name, mode];
assUnits => NotYetImpl;
skip => CantHappen;
ENDCASE => CaseMissing;
};
refLit: RefLiteralConstNode => CantHappen; --resolved in front end
numLiteral: REF NodeRep.const.numLiteral => {
SELECT numLiteral.class.kind FROM
real => SELECT TRUE FROM
numLiteral.class.precision=C2CTarget.bitsPerWord => cc ¬ SingleFloatLiteral[numLiteral.contents];
numLiteral.class.precision=C2CTarget.bitsPerDoubleWord => cc ¬ DoubleFloatLiteral[numLiteral.contents];
ENDCASE => CantHappen;
ENDCASE => CantHappen;
SELECT am FROM
plain, value => {};
ENDCASE => cc ¬ C2CAddressingOps.ModizeArithCode[cc, mode, numLiteral.class.precision];
};
ENDCASE => CaseMissing;
};
enterBlock: ROPE ¬ Rope.Flatten[Rope.Concat["{", C2CEmit.nestNLine]];
exitBlock: ROPE ¬ Rope.Flatten[Rope.Concat["};", C2CEmit.unNestNLine]];
GenBlockNode: PUBLIC PROC [blockNode: BlockNode, mode: Mode] RETURNS [cc: CodeCont] = {
saveBlockDecl, saveTempDecl: Code ¬ NIL;
allowsDecls: BOOL ¬
IF blockNode.bits#0
THEN FALSE
ELSE SELECT GetAMode[mode] FROM
skip, assBitAddr, assAddr, assUnits, assBits => TRUE,
ENDCASE => FALSE;
IF allowsDecls
THEN {
saveBlockDecl ¬ C2CEmit.CollectCode[blockDeclarations];
saveTempDecl ¬ C2CEmit.CollectCode[temporaryDeclarations];
}
ELSE {
s: INT ¬ BaseSize[mode];
IF s>0 AND s<blockNode.bits THEN mode ¬ SetBaseSize[mode, blockNode.bits];
};
cc ¬ GenNodeList[nodeList: blockNode.nodes, mode: mode, outsideTemporaryDecl: allowsDecls];
IF allowsDecls THEN {
decl1C: Code ¬ C2CEmit.CollectCode[blockDeclarations];
decl2C: Code ¬ C2CEmit.CollectCode[temporaryDeclarations];
IF decl1C#NIL OR decl2C#NIL THEN {
wasDead: BOOL ¬ cc.sc#NIL AND C2CEmit.GetIsDead[cc.sc];
cc.sc ¬ C2CEmit.Cat[enterBlock, decl1C, decl2C, cc.sc, exitBlock];
IF wasDead THEN C2CEmit.SetDead[cc.sc];
};
C2CEmit.AppendCode[blockDeclarations, saveBlockDecl];
C2CEmit.AppendCode[temporaryDeclarations, saveTempDecl];
};
};
IsLocalVar: PROC [varNode: Var] RETURNS [isLocalVariableNode: BOOL] = {
IF varNode = NIL THEN RETURN [FALSE];
WITH varNode.location SELECT FROM
localLocation: LocalVarLocation => RETURN [TRUE];
ENDCASE => RETURN [FALSE];
};
GenVarNodeInDeclaration: PROC [var: Var, init: Node¬NIL, mode: Mode, global: BOOL ¬ FALSE] RETURNS [initC: Code¬NIL] = {
--actually called from inside decl node, block node
--and from module node
GenInit: PROC [init: Node, var: Var, declPreC: Code, initInDeclAllowed: BOOL] RETURNS [declC, initC: Code¬NIL] = {
GenAssign: --IntCodeTwigImpl-- PROC [lhs: Var, rhs: Node] RETURNS [AssignNode] = {
lhs.flags[assigned] ¬ TRUE;
RETURN [IntCodeUtils.zone.NEW[NodeRep.assign ¬ [0, assign[lhs: lhs, rhs: rhs]]]];
};
declC ¬ declPreC;
IF init#NIL THEN {
IF var.bits#init.bits THEN CantHappen;
IF initInDeclAllowed AND var.bits=C2CTarget.bitsPerWord AND C2CPreprocessing.MayBeDeclaredAsPtr[var] THEN {
--it may and we do declare it as pointer, so it is put into an address register...
cc1: CodeCont ¬ GenNode[init, UseValue[init.bits]];
IF cc1.sc#NIL THEN CantHappen;
cc1.ec ¬ C2CEmit.MinPrecedence[cc1.ec, unaryPrecedence];
declC ¬ C2CEmit.Cat[declC, " = ", C2CTarget.wordPtrCast, cc1.ec];
}
ELSE IF initInDeclAllowed AND C2CIntCodeUtils.IsSimpleConst[init].is THEN {
--initialize right in declaration
--no casting: const is simple
cc1: CodeCont ¬ GenNode[init, UseValue[init.bits]];
IF cc1.sc#NIL THEN CantHappen;
declC ¬ C2CEmit.Cat[declC, " = ", cc1.ec];
}
ELSE {
--make separate statement for initialization
cc1: CodeCont;
assign: AssignNode;
assign ¬ GenAssign[lhs: var, rhs: init];
cc1 ¬ GenAssignNode[assignNode: assign, mode: skipMode];
initC ¬ cc1.sc;
IF cc1.ec#NIL THEN CantHappen;
};
};
};
PeekSpecialNames: PROC [] RETURNS [proposedName: ROPE¬NIL] = {
IF init#NIL AND var.bits=C2CTarget.bitsPerWord THEN
WITH init SELECT FROM
app: ApplyNode =>
WITH app.proc SELECT FROM
oper: OperNode =>
WITH oper.oper SELECT FROM
mesa: MesaOper =>
SELECT mesa.mesa FROM
alloc => RETURN ["lf"];
ENDCASE => {};
ENDCASE => {};
ENDCASE => {};
oper: OperNode =>
WITH oper.oper SELECT FROM
mesa: MesaOper =>
SELECT mesa.mesa FROM
globalFrame => RETURN ["gf"];
ENDCASE => {};
ENDCASE => {};
ENDCASE => {}
};
name: ROPE;
hasDecl: BOOL ¬ FALSE;
declC: Code ¬ NIL;
sz: INT ¬ C2CTarget.TemporaryBits[var.bits];
type: ROPE ¬ C2CTypes.DefineType[sz];
proposedName: ROPE ¬ "var";
IF var.bits=C2CTarget.bitsPerWord AND C2CPreprocessing.MayBeDeclaredAsPtr[var] THEN
type ¬ C2CTarget.wordPtr;
IF var.flags[frequent] AND ISTYPE[var.location, LocalVarLocation] AND var.bits=C2CTarget.bitsPerWord THEN {
--rely on preprocessing for eliminating "frequent" if troubles would arise
type ¬ Rope.Concat["register ", type];
proposedName ¬ PeekSpecialNames[].proposedName;
};
name ¬ C2CNames.VarName[id: var.id, class: proposedName];
WITH var.location SELECT FROM
localVarLocation: LocalVarLocation => {
IF global THEN CantHappenCedar;
hasDecl ¬ TRUE;
declC ¬ C2CEmit.Cat[type, " ", name];
IF localVarLocation.parent=nullLabel OR C2CBasics.labelWithLambda=NIL THEN CantHappen;
IF localVarLocation.parent.id#C2CBasics.labelWithLambda.label.id THEN CantHappen;
[declC, initC] ¬ GenInit[init: init, var: var, declPreC: declC, initInDeclAllowed: TRUE];
declC ¬ C2CEmit.Cat[declC, ";\n"];
IF var.bits#sz THEN
C2CBasics.Report[Rope.Cat["Warning: declares local variable ", name, " with funny size; This is benign if c2c doesn't crash on usage\n"]];
};
globalVarLocation: GlobalVarLocation => {
IF ~global THEN CantHappenCedar;
hasDecl ¬ TRUE;
declC ¬ C2CEmit.Cat["static ", type, " ", name];
[declC, initC] ¬ GenInit[init: init, var: var, declPreC: declC, initInDeclAllowed: TRUE];
declC ¬ C2CEmit.Cat[declC, ";\n"];
IF var.bits#sz THEN
C2CBasics.Report[Rope.Cat["Warning: declares global variable ", name, " with funny size; This is benign if c2c doesn't crash on usage\n"]];
};
fieldLocation: FieldLocation => {
declC ¬ C2CEmit.CatRemark[declC, Rope.Cat["declaration of ", name, " skipped"]];
IF init#NIL THEN
[declC, initC] ¬ GenInit[init: init, var: var, declPreC: declC, initInDeclAllowed: FALSE];
declC ¬ C2CEmit.Cat[declC, "\n"];
};
systemLocation: SystemLocation => CantHappenCedar;
registerLocation: RegisterLocation => CantHappenCedar;
linkLocation: LinkLocation => CantHappenCedar;
stackLocation: StackLocation => CantHappenCedar;
derefLocation: DerefLocation => CantHappenCedar;
indexedLocation: IndexedLocation => CantHappenCedar;
upLevelLocation: UpLevelLocation => CantHappenCedar;
compositeLocation: CompositeLocation => CantHappenCedar;
escapeLocation: EscapeLocation => CantHappenCedar;
dummyLocation: DummyLocation => CantHappenCedar;
ENDCASE => CaseMissing;
IF declC#NIL THEN {
IF global
THEN C2CEmit.AppendCode[procedureDeclarations, declC]
ELSE C2CEmit.AppendCode[blockDeclarations, declC];
};
};
GenDeclNode: PUBLIC PROC [declNode: DeclNode, mode: Mode] RETURNS [code: Code¬NIL] = {
code ¬ GenVarNodeInDeclaration[var: declNode.var, init: declNode.init, mode: mode];
};
LastNode: PROC [nodeList: IntCodeDefs.NodeList] RETURNS [node: IntCodeDefs.Node ¬ NIL] = {
WHILE nodeList#NIL DO
node ¬ nodeList.first;
nodeList ¬ nodeList.rest
ENDLOOP
};
GenEnableNode: PROC [enableNode: EnableNode, mode: Mode, skipPost: BOOL ¬ FALSE] RETURNS [cc: CodeCont] = {
nest: BOOL ¬ enableNode.handle#NIL;
sc, preCode, postCode: Code;
innerIsLive: BOOL ¬ IntCodeStuff.IsLive[LastNode[enableNode.scope]];
[sc, preCode, postCode] ¬ GenHandlerNode[handler: enableNode.handle, mode: mode, innerIsLive: innerIsLive];
IF skipPost THEN postCode ¬ NIL;
IF nest THEN C2CEnables.IncEnableNesting[];
cc ¬ GenNodeList[nodeList: enableNode.scope, mode: mode, outsideTemporaryDecl: FALSE];
cc.sc ¬ C2CEmit.Cat[sc, preCode, cc.sc, postCode];
IF cc.ec#NIL THEN CantHappen;
IF nest THEN C2CEnables.DecEnableNesting[];
};
GenCondNode: PUBLIC PROC [condNode: CondNode, mode: Mode] RETURNS [cc: CodeCont] = {
CondNodeIsSimpleEnoughForExpr: PROC [] RETURNS [b: BOOL ¬ FALSE] = {
IF condNode.bits>bitsPerWord OR condNode.bits=0 THEN RETURN [FALSE]
ELSE {
reqAMode: C2CAddressing.AddressMode ¬ GetAMode[mode];
SELECT reqAMode FROM
value, plain => {
RETURN [~C2CIntCodeUtils.StatementCode[condNode]]
};
skip, assUnits, assBits, assBitAddr => RETURN [FALSE];
ENDCASE => CaseMissing;
};
};
GenOrNodeList: PROC [nodeList: IntCodeDefs.NodeList] RETURNS [cc: CodeCont, thenLabel: ROPE¬NIL] = {
nodeList applied in context of if statement only [so position of boolean bit canm be ignored]
NeedsStatementCode: PROC [nodeList: IntCodeDefs.NodeList] RETURNS [BOOL¬FALSE] = {
FOR nl: NodeList ¬ nodeList, nl.rest WHILE nl#NIL DO
IF C2CIntCodeUtils.StatementCode[nl.first] THEN RETURN [TRUE];
ENDLOOP
};
isFirst: BOOL ¬ TRUE;
FOR nl: NodeList ¬ nodeList, nl.rest WHILE nl#NIL DO
cc1: CodeCont;
hackBool: BOOL ¬ C2CIntCodeUtils.IsFieldVar[nl.first];
IF hackBool THEN C2CBasics.PushContext[[$BoolBitHackOk, NIL, NIL]];
cc1 ¬ C2CAddressingOps.LoadArithNode[node: nl.first];
IF hackBool THEN C2CBasics.PopContext[];
IF cc1.sc#NIL THEN cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF isFirst
THEN cc.ec ¬ cc1.ec
ELSE cc.ec ¬ C2CEmit.BinOp[cc.ec, " || ", cc1.ec, logicalOrPrecedence];
isFirst ¬ FALSE;
IF NeedsStatementCode[nl.rest] THEN {
IF thenLabel=NIL THEN thenLabel ¬ C2CNames.InternalName["then0"];
cc.ec ¬ C2CEmit.MinPrecedence[cc.ec, allwaysPutParanthesisPrecedence];
cc.sc ¬ C2CEmit.Cat[cc.sc, "if ", cc.ec];
cc.sc ¬ C2CEmit.Cat[cc.sc, " { goto ", thenLabel, ";};\n"];
cc.ec ¬ NIL;
isFirst ¬ TRUE;
};
ENDLOOP;
cc.ec ¬ C2CEmit.MinPrecedence[cc.ec, logicalOrPrecedence];
};
ExprCond: PROC [] = {
count: INT ¬ 0; --we count open parantheses
code: Code ¬ C2CEmit.RopeCode[];
FOR cases: IntCodeDefs.CaseList ¬ condNode.cases, cases.rest WHILE cases#NIL DO
IF cases.tests=NIL THEN {
--last case
elsecc: CodeCont;
IF cases.rest#NIL THEN CantHappen;
elsecc ¬ C2CAddressingOps.LoadArithNode[node: cases.body];
SIZE PROBLEM elsecc ← GenNode[node: cases.body, mode: mode];
elsecc.ec ¬ C2CEmit.MinPrecedence[elsecc.ec, questionColonPrecedence];
IF elsecc.sc#NIL THEN CantHappen;
code ¬ C2CEmit.Cat[code, elsecc.ec];
}
ELSE {
--other case
testcc, bodycc: CodeCont; thenLabel: ROPE ¬ NIL;
[testcc, thenLabel] ¬ GenOrNodeList[nodeList: cases.tests];
IF thenLabel#NIL THEN CantHappen;
IF C2CEmit.NonWhiteSpace[testcc.sc] THEN CantHappen; --shouldn't have used Expr
testcc.ec ¬ C2CEmit.MinPrecedence[testcc.ec, parenPrecedence];
bodycc ¬ C2CAddressingOps.LoadArithNode[node: cases.body];
SIZE PROBLEM bodycc ← GenNode[node: cases.body, mode: mode];
IF C2CEmit.NonWhiteSpace[bodycc.sc] THEN CantHappen; --shouldn't have used Expr
bodycc.ec ¬ C2CEmit.MinPrecedence[bodycc.ec, questionColonPrecedence];
code ¬ C2CEmit.Cat[code, " ( ", testcc.ec]; count ¬ count+1;
code ¬ C2CEmit.Cat[code, " ? ", bodycc.ec, " : "];
}
ENDLOOP;
IF count=0 THEN CantHappen;
WHILE count>0 DO
code ¬ C2CEmit.Cat[code, " ) "]; count ¬ count-1;
ENDLOOP;
code ¬ C2CEmit.SetPrecedence[code, parenPrecedence];
cc.ec ¬ code;
};
CanSwitchStatementBeUsed: PROC RETURNS [switchVar: Var ¬ NIL] = {
--returns switchVar#NIL if a switch statement can be used
branchTab: IntCodeUtils.IdTab ¬ IntCodeUtils.NewIdTab[];
branches: INT ¬ 0;
CheckOneTest: PROC [n: Node] RETURNS [switch: BOOL ¬ TRUE] = {
IF n.bits#1 THEN RETURN [FALSE];
WITH n SELECT FROM
apply: ApplyNode => {
isConst: BOOL; constVal: CARD;
--check operation
IF apply.handler#NIL THEN RETURN [FALSE];
IF apply.args=NIL OR apply.args.rest=NIL OR apply.args.rest.rest#NIL THEN RETURN [FALSE];
WITH apply.proc SELECT FROM
oper: OperNode =>
WITH oper.oper SELECT FROM
compare: CompareOper => {
IF compare.class.precision>C2CTarget.bitsPerWord THEN RETURN [FALSE];
IF compare.sense#eq THEN RETURN [FALSE];
SELECT compare.class.kind FROM
signed, unsigned => {};
ENDCASE => RETURN [FALSE]
};
ENDCASE => RETURN [FALSE];
ENDCASE => RETURN [FALSE];
--check constant
[isConst, constVal] ¬ C2CIntCodeUtils.IsSimpleConst[apply.args.rest.first];
IF ~isConst THEN RETURN [FALSE];
IF IntCodeUtils.Insert[branchTab, LOOPHOLE[constVal], $x]#IntCodeUtils.NullValue THEN RETURN [FALSE];
--check variable
WITH apply.args.first SELECT FROM
var: Var => {
IF switchVar#NIL
THEN {
IF switchVar.id#var.id THEN RETURN [FALSE];
}
ELSE {
IF var.bits>C2CTarget.bitsPerWord THEN RETURN [FALSE];
switchVar ¬ var;
};
};
ENDCASE => RETURN [FALSE];
};
ENDCASE => RETURN [FALSE];
};
FOR cases: IntCodeDefs.CaseList ¬ condNode.cases, cases.rest WHILE cases#NIL DO
IF cases.tests#NIL THEN {
FOR nl: NodeList ¬ cases.tests, nl.rest WHILE nl#NIL DO
switch: BOOL ¬ CheckOneTest[nl.first];
branches ¬ branches+1;
IF ~switch THEN RETURN [NIL];
ENDLOOP;
};
ENDLOOP;
IF branches<3 THEN RETURN [NIL];
};
StatementCondWithSwitch: PROC [switchVar: Var] = {
noneAlive: BOOL ¬ TRUE;
hadDefault: BOOL ¬ FALSE;
cc1: CodeCont ¬ C2CAddressingOps.LoadArithNode[node: switchVar];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
cc.sc ¬ C2CEmit.Cat[cc.sc, "switch (", cc1.ec, ") {", C2CEmit.nestNLine];
FOR cases: IntCodeDefs.CaseList ¬ condNode.cases, cases.rest WHILE cases#NIL DO
IF cases.tests=NIL
THEN {
cc.sc ¬ C2CEmit.Cat[cc.sc, "default: "];
hadDefault ¬ TRUE
}
ELSE {
FOR nl: NodeList ¬ cases.tests, nl.rest WHILE nl#NIL DO
WITH nl.first SELECT FROM
apply: ApplyNode => {
--possibly machine dependent: not every C allows unsigned switch statements
val: CARD ¬ C2CIntCodeUtils.IsSimpleConst[apply.args.rest.first].val;
cc.sc ¬ C2CEmit.Cat[cc.sc, IO.PutFR1["case %g: ", IO.card[val]]];
};
ENDCASE => ERROR;
ENDLOOP
};
cc.sc ¬ C2CEmit.Cat[cc.sc, C2CEmit.nestNLine];
cc1 ¬ GenNode[node: cases.body, mode: mode];
cc.sc ¬ Cat2[cc.sc, cc1.sc]; IF cc1.ec#NIL THEN CantHappen;
IF C2CEmit.GetIsDead[cc.sc]
THEN cc.sc ¬ C2CEmit.Cat[cc.sc, C2CEmit.unNestNLine]
ELSE {
cc.sc ¬ C2CEmit.Cat[cc.sc, "break;", C2CEmit.unNestNLine];
noneAlive ¬ FALSE;
};
ENDLOOP;
cc.sc ¬ C2CEmit.Cat[cc.sc, "};", C2CEmit.unNestNLine];
IF noneAlive AND hadDefault THEN C2CEmit.SetDead[cc.sc];
};
StatementCondWithIfs: PROC [] = {
cc1: CodeCont;
isFirst: BOOL ¬ TRUE;
elseBrackets: INT ¬ 0;
allDead: BOOL ¬ condNode.cases#NIL;
ifBracket: BOOL ¬ FALSE;
FOR cases: IntCodeDefs.CaseList ¬ condNode.cases, cases.rest WHILE cases#NIL DO
hasAnElse: BOOL ¬ cases.rest#NIL;
ifBracket ¬ FALSE;
IF ~isFirst THEN {
elseBrackets ¬ elseBrackets+1;
cc.sc ¬ C2CEmit.Cat[cc.sc, "else {", C2CEmit.nestNLine];
};
IF cases.tests#NIL
THEN {
testcc: CodeCont; thenLabel: ROPE ¬ NIL;
[testcc, thenLabel] ¬ GenOrNodeList[nodeList: cases.tests];
cc.sc ¬ Cat2[cc.sc, testcc.sc];
testcc.ec ¬ C2CEmit.MinPrecedence[testcc.ec, allwaysPutParanthesisPrecedence];
ifBracket ¬ TRUE;
cc.sc ¬ C2CEmit.Cat[cc.sc, "if ", testcc.ec, " {", C2CEmit.nestNLine];
IF thenLabel#NIL THEN
cc.sc ¬ C2CEmit.Cat[cc.sc, thenLabel, ": ;\n"];
};
cc1 ¬ GenNode[node: cases.body, mode: mode];
IF allDead AND ~C2CEmit.GetIsDead[cc1.sc] THEN allDead ¬ FALSE;
cc.sc ¬ C2CEmit.Cat[cc.sc, cc1.sc];
IF cc1.ec#NIL THEN CantHappen;
IF ifBracket THEN {
cc.sc ¬ C2CEmit.Cat[cc.sc, "}",
(IF hasAnElse THEN NIL ELSE ";"),
C2CEmit.unNestNLine
];
};
isFirst ¬ FALSE;
ENDLOOP;
FOR i: INT IN [0..elseBrackets) DO
cc.sc ¬ C2CEmit.Cat[cc.sc, "};", C2CEmit.unNestNLine];
ENDLOOP;
IF allDead AND ~ifBracket THEN C2CEmit.SetDead[cc.sc];
};
LongStatementCondWithIfs: PROC [] = {
cc1: CodeCont;
elseBrackets: INT ¬ 0;
endLabel: ROPE ¬ C2CNames.InternalName["endif0"];
needsEndLabel: BOOL ¬ FALSE;
allDead: BOOL ¬ condNode.cases#NIL;
isIf: BOOL ¬ FALSE;
FOR cases: IntCodeDefs.CaseList ¬ condNode.cases, cases.rest WHILE cases#NIL DO
isIf ¬ FALSE;
IF cases.tests#NIL THEN {
testcc: CodeCont; thenLabel: ROPE ¬ NIL;
[testcc, thenLabel] ¬ GenOrNodeList[nodeList: cases.tests];
cc.sc ¬ Cat2[cc.sc, testcc.sc];
testcc.ec ¬ C2CEmit.MinPrecedence[testcc.ec, allwaysPutParanthesisPrecedence];
isIf ¬ TRUE;
cc.sc ¬ C2CEmit.Cat[cc.sc, "if ", testcc.ec, " {", C2CEmit.nestNLine];
IF thenLabel#NIL THEN
cc.sc ¬ C2CEmit.Cat[cc.sc, thenLabel, ": ;\n"];
};
cc1 ¬ GenNode[node: cases.body, mode: mode];
IF allDead AND ~C2CEmit.GetIsDead[cc1.sc] THEN allDead ¬ FALSE;
cc.sc ¬ C2CEmit.Cat[cc.sc, cc1.sc];
IF cc1.ec#NIL THEN CantHappen;
IF ~C2CEmit.GetIsDead[cc.sc] THEN {
cc.sc ¬ C2CEmit.Cat[cc.sc, "goto ", endLabel, ";\n"];
allDead ¬ FALSE;
needsEndLabel ¬ TRUE;
};
IF isIf THEN
cc.sc ¬ C2CEmit.Cat[cc.sc, "};", C2CEmit.unNestNLine];
ENDLOOP;
IF needsEndLabel THEN cc.sc ¬ C2CEmit.Cat[cc.sc, endLabel, ": ;\n"];
IF allDead AND ~isIf THEN C2CEmit.SetDead[cc.sc];
};
IsLongCond: PROC [condList: IntCodeDefs.CaseList] RETURNS [BOOL¬FALSE] = {
cnt: INT ¬ 0;
FOR l: IntCodeDefs.CaseList ¬ condList, l.rest WHILE l#NIL DO
IF (cnt ¬ cnt+1)>=4 THEN RETURN [TRUE]
ENDLOOP
};
StatementCond: PROC [] = {
switchVar: Var ¬ CanSwitchStatementBeUsed[];
SELECT TRUE FROM
switchVar#NIL => StatementCondWithSwitch[switchVar];
IsLongCond[condNode.cases] => LongStatementCondWithIfs[]
ENDCASE => StatementCondWithIfs[];
};
aMode: C2CAddressing.AddressMode ¬ GetAMode[mode];
IF LHSMode[mode] THEN NotYetImpl;
SELECT aMode FROM
skip, assUnits, assBits, assBitAddr, assAddr => StatementCond[];
value, maskNShift, plain => {
IF CondNodeIsSimpleEnoughForExpr[] THEN ExprCond[]
ELSE {
bits: INT ¬ C2CTarget.TemporaryBits[condNode.bits];
tempName: ROPE ¬ C2CStateUtils.DeclareVariable[temporaryDeclarations, bits, "tc"];
cc ¬ GenNode[condNode, SetAssUnits[mode, tempName, bits]];
IF cc.ec#NIL THEN CantHappen;
cc.ec ¬ C2CEmit.IdentCode[tempName];
}
};
getAddr => {
IF CondNodeIsSimpleEnoughForExpr[] THEN ExprCond[]
ELSE {
tempName: ROPE ¬ C2CStateUtils.DeclareVariable[temporaryDeclarations, C2CTarget.bitsPerWord, "tcp"];
cc ¬ GenNode[condNode, SetAssAddr[mode, tempName]];
IF cc.ec#NIL THEN CantHappen;
cc.ec ¬ C2CEmit.IdentCode[tempName];
}
};
ENDCASE => CaseMissing;
};
GenLabelNode: PUBLIC PROC [labelNode: LabelNode, mode: Mode] RETURNS [cc: CodeCont] = {
WITH labelNode.label.node SELECT FROM
labeledLambda: LambdaNode => {
--Label for a procedure.
outerLambda: LabelNode ¬ C2CBasics.labelWithLambda;
C2CBasics.labelWithLambda ¬ labelNode;
GenLambdaNodeWithLabels[labeledLambda, labelNode, mode];
C2CBasics.labelWithLambda ¬ outerLambda;
};
ENDCASE => {
--Ordinary label
IF labelNode.label.id#nullLogicalId THEN
cc.sc ¬ C2CEmit.Cat[C2CNames.LabName[id: labelNode.label.id, class: "lab"], ": ;\n"];
IF labelNode.label.node#NIL THEN {
cc1: CodeCont ¬ C2CMain.GenNode[node: labelNode.label.node, mode: mode];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF cc1.ec#NIL THEN CantHappen;
};
};
};
GenGotoNode: PUBLIC PROC [gotoNode: GotoNode, mode: Mode] RETURNS [code: Code¬NIL] = {
name: ROPE;
SELECT GetAMode[mode] FROM
skip => {};
ENDCASE => CantHappen;
name ¬ C2CNames.LabName[gotoNode.dest.id, "lab"];
code ¬ C2CEmit.Cat["goto ", name, ";\n"];
FOR i: INT IN [0..C2CEnables.PopsForJump[gotoNode.dest.id]) DO
code ¬ C2CEmit.Cat[C2CRunTime.PopHandler[], ";\n", code];
ENDLOOP;
C2CEmit.SetDead[code];
};
GenLambdaNode: PUBLIC PROC [lambdaNode: LambdaNode, mode: Mode] RETURNS [code: Code¬NIL] = {
--Unlabeled lambda node! How do we get here, and what can we do about it?
-- I guess I could make up labels and call GenLambdaNodeWithLabels.
CantHappenCedar;
};
GenLambdaNodeWithLabels: PUBLIC PROC [lambdaNode: LambdaNode, labelNode: LabelNode, mode: Mode] = {
myFlags: Mode ¬ mode;
RVar: TYPE = RECORD [r: ROPE, var: Var];
addressTab: IntCodeUtils.IdTab ¬ IntCodeUtils.NewIdTab[];
--contains names of pointers for indirectly passed things
GenFormalList: PROC [varList: VarList] RETURNS [param: Code¬NIL] = {
--generates the list naming the formals
IF ExpMode[mode] THEN CantHappen;
FOR list: VarList ¬ varList, list.rest WHILE list#NIL DO
var: Var ¬ list.first;
name: ROPE ¬ C2CNames.VarName[id: var.id, class: "formal"];
IF var.location#nullLocation THEN {
WITH var.location SELECT FROM
locLoc: LocalVarLocation =>
IF locLoc.parent.id#C2CBasics.labelWithLambda.label.id THEN CantHappen;
ENDCASE => CantHappen;
};
IF var.bits<=C2CTarget.maxBitsForValueParams
THEN {
param ¬ C2CEmit.Cat[param, name]
}
ELSE {
ptrName: ROPE ¬ C2CNames.InternalName[Rope.Concat["P", name]];
param ¬ C2CEmit.Cat[param, ptrName];
[] ¬ IntCodeUtils.Store[addressTab, var.id, ptrName];
};
IF list.rest#NIL THEN param ¬ C2CEmit.Cat[param, ", "];
ENDLOOP;
};
FormalsDecl: PROC [varList: VarList] RETURNS [code: Code¬NIL] = {
--generates the list declaring the named formals
FOR list: VarList ¬ varList, list.rest WHILE list#NIL DO
var: Var ¬ list.first;
val: IntCodeUtils.Value ¬ IntCodeUtils.Fetch[addressTab, var.id];
cc1: Code;
IF val=IntCodeUtils.NullValue
THEN {
cc1 ¬ GenVarNodeInDeclaration[var: var, init: NIL, mode: declMode, global: FALSE]
}
ELSE {
pType: ROPE ¬ C2CTypes.DefinePtrType[var.bits];
cc1 ¬ C2CEmit.Cat[pType, " ", NARROW[val, ROPE], ";"];
};
code ¬ C2CEmit.Cat[code, cc1, C2CEmit.line];
ENDLOOP;
};
DeclareNMoveLargeFormals: PROC [varList: VarList] RETURNS [code: Code¬NIL] = {
--generates declaration for formals which are copied; including code
FOR list: VarList ¬ varList, list.rest WHILE list#NIL DO
var: Var ¬ list.first;
val: IntCodeUtils.Value ¬ IntCodeUtils.Fetch[addressTab, var.id];
IF val=IntCodeUtils.NullValue THEN NULL
ELSE {
addrName: ROPE ¬ NARROW[val];
usedName: ROPE ¬ C2CNames.VarName[id: var.id, class: "formal"];
decl: Code ¬ GenVarNodeInDeclaration[var: var, init: NIL, mode: declMode, global: FALSE];
C2CEmit.AppendCode[procedureDeclarations, C2CEmit.Cat[decl, C2CEmit.line]];
code ¬ C2CEmit.Cat[
code,
C2CRunTime.MoveWordsDisjoint[
src: C2CEmit.IdentCode[addrName],
dst: C2CEmit.Cat["&", usedName],
nWords: C2CTarget.BitsToWords[var.bits] --rounds up same as template
],
";\n"
];
};
ENDLOOP;
};
cc1: CodeCont;
procName: ROPE;
staticOrExtern: ROPE ¬ IF C2CNames.IsExtern[labelNode.label.id] THEN "extern " ELSE "static ";
param, headCode, mainCode, total: Code;
formalReturnName: ROPE;
formalReturnType: ROPE ¬
IF (lambdaNode.bitsOut>0) AND (lambdaNode.bitsOut<=C2CTarget.bitsPerWord) THEN "word " ELSE "void ";
formalArgs: VarList ~ lambdaNode.formalArgs;
myFlags ¬ SetExpr[myFlags, FALSE];
IF GetProp[myKeyForModuleEncountered]=NIL THEN CantHappen;
PutProp[myKeyForReturnBits, NEW[INT¬lambdaNode.bitsOut]];
IF GetProp[myKeyForFirstProc]=NIL
THEN {
procName ¬ C2CNames.LabName[id: labelNode.label.id, class: "Installation"];
PutProp[myKeyForFirstProc, procName];
}
ELSE {
procName ¬ C2CNames.LabName[id: labelNode.label.id, class: "Proc"];
};
C2CEmit.AppendCode[moduleDeclarationsP, C2CEmit.Cat[staticOrExtern, formalReturnType, procName, "();\n"]];
headCode ¬ C2CEmit.Cat[C2CEmit.twoLines, staticOrExtern, formalReturnType, procName, "("];
IF lambdaNode.bitsOut>C2CTarget.bitsPerWord THEN {
formalReturnName ¬ C2CNames.InternalName["formalReturn"];
PutProp[myKeyForFormalReturn, formalReturnName];
headCode ¬ C2CEmit.Cat[headCode, formalReturnName];
IF formalArgs#NIL THEN headCode ¬ C2CEmit.Cat[headCode, ", "];
};
param ¬ GenFormalList[varList: formalArgs];
headCode ¬ C2CEmit.Cat[headCode, param, ")", C2CEmit.nestNLine];
headCode ¬ C2CEmit.Cat[headCode, FormalsDecl[varList: formalArgs]];
IF lambdaNode.bitsOut>C2CTarget.bitsPerWord THEN {
headCode ¬ C2CEmit.Cat[headCode, "word ", formalReturnName, "[];", C2CEmit.line];
};
headCode ¬ C2CEmit.Cat[
headCode,
C2CEmit.CollectCode[procedureDeclarations],
C2CEmit.CollectCode[blockDeclarations],
C2CEmit.CollectCode[temporaryDeclarations]
];
headCode ¬ C2CEmit.Cat[headCode, C2CEmit.line, "{", C2CEmit.line];
mainCode ¬ DeclareNMoveLargeFormals[formalArgs];
cc1 ¬ GenNodeList[nodeList: lambdaNode.body, mode: myFlags, outsideTemporaryDecl: TRUE, mayOmmitLastEnablePop: lambdaNode.bitsOut>0];
IF cc1.ec#NIL THEN CantHappen;
mainCode ¬ C2CEmit.Cat[
C2CEmit.CollectCode[procedureDeclarations],
C2CEmit.CollectCode[blockDeclarations],
C2CEmit.CollectCode[temporaryDeclarations],
mainCode,
cc1.sc
];
mainCode ¬ C2CEmit.Cat[mainCode, "}", C2CEmit.unNest, C2CEmit.twoLines];
PutProp[myKeyForFormalReturn, NIL];
PutProp[myKeyForReturnBits, NIL];
total ¬ C2CEmit.Cat[
headCode,
C2CEmit.CollectCode[procedureDeclarations],
C2CEmit.CollectCode[blockDeclarations],
C2CEmit.CollectCode[temporaryDeclarations],
mainCode
];
C2CEmit.AppendCode[moduleContents, total];
FreeMode[myFlags];
};
GenReturnNode: PUBLIC PROC [returnNode: ReturnNode, mode: Mode] RETURNS [cc: CodeCont] = {
Hint: there are return nodes with 0 size! these nodes need to be executed before the return
cc1: CodeCont;
returnBits: INT;
pops: INT ¬ C2CEnables.PopsForReturns[];
myMode: Mode ¬ SetExpr[mode, TRUE];
skipMode: Mode ¬ SetAMode[myMode, skip];
DoPops: PROC [] RETURNS [c: Code¬NIL] = {
FOR i: INT IN [0..pops) DO
c ¬ C2CEmit.Cat[c, C2CRunTime.PopHandler[], ";\n"];
ENDLOOP;
};
WITH GetProp[myKeyForReturnBits] SELECT FROM
i: REF INT => returnBits ¬ i­;
ENDCASE => CantHappen;
IF returnBits=0 THEN {
FOR nodes: NodeList ¬ returnNode.rets, nodes.rest WHILE nodes#NIL DO
IF nodes.first.bits#0 THEN CantHappen;
cc1 ¬ GenNode[nodes.first, skipMode];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF cc1.ec#NIL THEN CantHappen;
ENDLOOP;
cc.sc ¬ C2CEmit.Cat[cc.sc, DoPops[], "return;\n"]
}
ELSE IF returnBits<=C2CTarget.bitsPerWord THEN {
retVal: Code ¬ NIL;
mustUseTemporary: BOOL ¬ FALSE;
IF pops#0 AND returnBits#0 THEN {
retVal ¬ C2CEmit.IdentCode[C2CStateUtils.DeclareVariable[procedureDeclarations, C2CTarget.bitsPerWord, "temp"]];
mustUseTemporary ¬ TRUE;
};
FOR nodes: NodeList ¬ returnNode.rets, nodes.rest WHILE nodes#NIL DO
node: Node ¬ nodes.first;
IF node.bits=0 THEN {
cc1 ¬ GenNode[node, skipMode];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF cc1.ec#NIL THEN CantHappen;
}
ELSE {
m: Mode ¬ UseValue[node.bits, myMode];
IF node.bits#returnBits THEN CantHappen;
cc1 ¬ GenNode[node, m]; FreeMode[m];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF nodes.rest#NIL THEN {
IF ~mustUseTemporary THEN {
retVal ¬ C2CEmit.IdentCode[C2CStateUtils.DeclareVariable[procedureDeclarations, C2CTarget.bitsPerWord, "temp"]];
mustUseTemporary ¬ TRUE;
};
};
IF mustUseTemporary
THEN {
cc1.ec ¬ C2CEmit.MinPrecedence[cc1.ec, assignPrecedence];
cc.sc ¬ C2CEmit.Cat[cc.sc, C2CEmit.CopyC[retVal], " = ", cc1.ec, ";\n"];
}
ELSE retVal ¬ cc1.ec;
};
ENDLOOP;
cc.sc ¬ C2CEmit.Cat[cc.sc, DoPops[], "return(", retVal, ");\n"];
}
ELSE {
--returnBits>C2CTarget.bitsPerWord
i: INT ¬ 0;
FOR nodes: NodeList ¬ returnNode.rets, nodes.rest WHILE nodes#NIL DO
nodeMode: Mode;
node: Node ¬ nodes.first;
IF (node.bits MOD C2CTarget.bitsPerWord)#0 THEN CantHappen;
IF node.bits=0
THEN nodeMode ¬ SetAMode[myMode, skip]
ELSE nodeMode ¬ UseValue[node.bits, myMode];
cc1 ¬ GenNode[node, nodeMode];
cc.sc ¬ Cat2[cc.sc, cc1.sc];
IF node.bits=0
THEN {
IF cc1.ec#NIL THEN CantHappen;
}
ELSE {
formalReturn: ROPE ¬ NARROW[GetProp[myKeyForFormalReturn]];
cc.sc ¬ C2CEmit.Cat[
cc.sc,
IO.PutFR["%g[%g] = ", IO.rope[formalReturn], IO.int[i]],
cc1.ec,
";\n"
];
i ¬ i+1;
};
FreeMode[nodeMode];
ENDLOOP;
cc.sc ¬ C2CEmit.Cat[cc.sc, DoPops[], "return;\n"];
};
C2CEmit.SetDead[cc.sc];
FreeMode[skipMode];
FreeMode[myMode];
};
GenGlobalFrame: PROC [] RETURNS [code: Code] = {
name: ROPE ¬ C2CGlobalFrame.GlobalFrameName[];
code ¬ C2CEmit.Cat["&", name];
code ¬ C2CEmit.SetPrecedence[code, unaryPrecedence];
};
GenNakedOperNode: PROC [operNode: OperNode, mode: Mode] RETURNS [cc: CodeCont] = {
--Mostly oper nodes are applied, and as such are handled inside GenApplyNode.
NakedMesaOp: PROC [mesaOper: MesaOper, mode: Mode] RETURNS [cc: CodeCont] = {
SELECT mesaOper.mesa FROM
globalFrame => cc.ec ¬ GenGlobalFrame[];
unnamedError => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedUnnamedError];
unwindError => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedUnwindError];
abortedError => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedAbortedError];
uncaughtError => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedUncaughtError];
boundsError => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedBoundsError];
narrowFault => cc.ec ¬ C2CEmit.IdentCode[C2CRunTime.nakedNarrowFault];
addr, all, equal, notEqual, nilck, alloc, free, fork, join, monitorEntry, monitorExit, notify, broadcast, wait, signal, error, unwind, resume, reject, copyGlobal, startGlobal, restartGlobal, stopGlobal, checkInit => CantHappenCedar;
--Should always be applied:
--The mesa language does not have the primitives to use as value
ENDCASE => CaseMissing;
};
NakedCedarOp: PROC [cedarOper: CedarOper, mode: Mode] RETURNS [cc: CodeCont] = {
SELECT cedarOper.cedar FROM
procCheck => {
NotYetImpl; --cedar oper proc check
};
ENDCASE => CaseMissing; --mesa oper
};
NakedCodeOp: PROC [codeOper: CodeOper, mode: Mode] RETURNS [cc: CodeCont] = {
name: ROPE;
label: Label ¬ codeOper.label;
cast: ROPE ¬ C2CTypes.DefineFTypeCast[];
IF codeOper.offset#0 THEN CantHappenCedar;
name ¬ C2CNames.LabName[codeOper.label.id, "Proc"];
cc.ec ¬ C2CEmit.Cat[" ((word) ", cast, name, ") "];
};
WITH operNode.oper SELECT FROM
mesaOp: MesaOper => cc ¬ NakedMesaOp[mesaOp, mode];
cedarOp: CedarOper => cc ¬ NakedCedarOp[cedarOp, mode];
codeOp: CodeOper => cc ¬ NakedCodeOp[codeOp, mode];
--the other operators are not allowed to be naked
ENDCASE => CantHappenCedar;
};
GenModuleNode: PROC [moduleNode: ModuleNode, mode: Mode] = {
cc1: CodeCont; gFrameCode: Code;
IF GetProp[myKeyForModuleEncountered]#NIL THEN CantHappenCedar;
PutProp[myKeyForModuleEncountered, $yes];
gFrameCode ¬ C2CGlobalFrame.GlobalFrameDeclarationCode[moduleNode];
C2CEmit.AppendCode[globalFrameDeclaration, gFrameCode];
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[procedureDeclarations]];
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[blockDeclarations]];
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[temporaryDeclarations]];
cc1 ¬ GenNodeList[nodeList: moduleNode.procs, mode: SetExpr[mode, FALSE], outsideTemporaryDecl: TRUE];
IF cc1.ec#NIL THEN CantHappen;
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[procedureDeclarations]];
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[blockDeclarations]];
C2CEmit.AppendCode[moduleContents, C2CEmit.CollectCode[temporaryDeclarations]];
C2CEmit.AppendCode[moduleContents, cc1.sc];
};
sourceEnterMacro: ROPE ¬ C2CNames.Reserve["SOURCE"];
sourceExitMacro: ROPE ← C2CNames.Reserve["SOURCEPOP"]; --Not used
sourceProgName: ROPE ¬ C2CNames.Reserve["progName"];
enterFormat: ROPE ¬ Rope.Flatten[Rope.Concat[C2CEmit.noIndent, "%g(%g, %g)\n"]];
temporarySourcePos: REF TEXT ¬ RefText.New[11];
sourceStuffInitialized: BOOL ¬ FALSE;
sourceAsMacro: BOOL ¬ FALSE;
sourceInFile: BOOL ¬ FALSE;
ResetSourceStuff: PROC [] = {
sourceStuffInitialized ¬ FALSE
};
InitSourceStuff: PROC [] = {
sourceStuffInitialized ¬ TRUE;
sourceAsMacro ¬ C2CAccess.params.generateSourceMacros;
IF sourceAsMacro THEN {
enterMacro: ROPE ¬ Rope.Concat["#define ", sourceEnterMacro];
IF C2CAccess.params.generateDBXStyleSourceMacros
THEN enterMacro ¬ Rope.Cat[enterMacro, "(p, l)# 123/**/p/**/00 """, C2CNames.ProgramName[], ".mesa"" /* l */\n"]
ELSE enterMacro ¬ Rope.Concat[enterMacro, "(p, l) /* source p, l */\n"];
C2CEmit.AppendCode[macroDeclarations, enterMacro];
sourceAsMacro ¬ TRUE;
};
sourceInFile ¬ C2CAccess.params.generateLineNumberStream;
IF sourceInFile THEN {
temporarySourcePos.length ¬ 10;
temporarySourcePos[0] ¬ C2CEmit.breakChar;
};
};
DefineSourceEnter: PROC [] RETURNS [name: ROPE] = INLINE {
name ¬ sourceEnterMacro;
};
GenSourceNode: PUBLIC PROC [sourceNode: SourceNode, mode: Mode] RETURNS [cc: CodeCont] = {
whiteSpace: BOOL;
IF ~sourceStuffInitialized THEN InitSourceStuff[];
cc ¬ GenNodeList[nodeList: sourceNode.nodes, mode: mode, outsideTemporaryDecl: FALSE];
IF sourceNode.source=IntCodeDefs.nullSourceRange THEN RETURN;
IF sourceNode.source.file#0 THEN RETURN; --file change!
IF cc.ec#NIL OR cc.xbc#NIL THEN RETURN; --position would not be exact, better ommit
whiteSpace ¬ ~C2CEmit.NonWhiteSpace[cc.sc];
IF whiteSpace THEN RETURN; --I fear those positions might be duplicated and cause problems
IF sourceNode.source.chars=0 THEN RETURN; --Just to avoid problems
BEGIN
wasDead: BOOL ¬ C2CEmit.GetIsDead[cc.sc];
outerSourcePosition: IntCodeDefs.SourceNode ¬ C2CSourcePositions.currentSourceNode;
C2CSourcePositions.currentSourceNode ¬ sourceNode;
IF outerSourcePosition#NIL AND outerSourcePosition.source = sourceNode.source THEN RETURN; --avoid identical ranges; at least where direct and easy
IF sourceAsMacro THEN {
enter: Rope.ROPE ¬ IO.PutFR[enterFormat, [rope[DefineSourceEnter[]]], [integer[sourceNode.source.start]], [integer[sourceNode.source.chars]]];
cc.sc ¬ C2CEmit.Cat[enter, cc.sc];
};
IF sourceInFile THEN {
enter, exit: Rope.ROPE ¬ NIL;
start: INT ¬ sourceNode.source.start;
chars: INT ¬ sourceNode.source.chars;
temporarySourcePos[2]  ¬ 0C + start  / 100000000B MOD 256;
temporarySourcePos[3]  ¬ 0C + start  / 200000B MOD 256;
temporarySourcePos[4]  ¬ 0C + start  / 256 MOD 256;
temporarySourcePos[5]  ¬ 0C + start MOD 256;
temporarySourcePos[6]  ¬ 0C + chars / 100000000B MOD 256;
temporarySourcePos[7]  ¬ 0C + chars / 200000B MOD 256;
temporarySourcePos[8]  ¬ 0C + chars / 256 MOD 256;
temporarySourcePos[9] ¬ 0C + chars MOD 256;
temporarySourcePos[1] ¬ '#;
enter ¬ Rope.FromRefText[temporarySourcePos];
temporarySourcePos[1] ¬ '%;
exit ¬ Rope.FromRefText[temporarySourcePos];
cc.sc ¬ C2CEmit.Cat[enter, cc.sc, exit];
};
IF whiteSpace THEN cc.sc ¬ C2CEmit.SetWhiteSpace[cc.sc];
IF wasDead THEN C2CEmit.SetDead[cc.sc];
C2CSourcePositions.currentSourceNode ¬ outerSourcePosition;
END;
};
GenCommentNode: PUBLIC PROC [commentNode: CommentNode, mode: Mode] RETURNS [code: Code¬NIL] = {
code ¬ C2CEmit.Cat[C2CEmit.CComment[commentNode.bytes]];
IF ~ExpMode[mode] THEN {
code ¬ C2CEmit.Cat[C2CEmit.line, code, C2CEmit.line];
};
code ¬ C2CEmit.SetWhiteSpace[code];
};
magic: Rope.ROPE ¬ "/* Generated with C2C (Cedar To C)*/\n";
copyright: Rope.ROPE ¬ Rope.Flatten[IO.PutFR1["/* Copyright (C) %g by Xerox Corporation. All rights reserved. */\n", IO.int[BasicTime.Unpack[BasicTime.Now[]].year]]];
UseReferenceCounting: PROC [] RETURNS [use: BOOL] = {
Find out whether the ref counting primitives ought to be used.
Sorry, we put the burden inside here instead of C2CRuntime because that allows ommiting the typecodes.
RETURN [C2CAccess.params.supportReferenceCounting]
};
C2CRoot: PUBLIC PROC [] RETURNS [code: Code] = {
GenMain: PROC [node: Node] = {
maincc: CodeCont;
progName: ROPE ¬ C2CNames.ProgramName[];
firtProcName: ROPE;
moduleInitCode, mainCode: Code ¬ NIL;
C2CEmit.AppendCode[moduleHeader, magic];
C2CEmit.AppendCode[moduleHeader, copyright];
C2CEmit.AppendCode[moduleHeader, IO.PutFR1["/* time: %g */\n", IO.time[]]];
C2CEmit.AppendCode[moduleHeader,
Rope.Cat["/* C2C version: ", C2CBasics.c2cVersion, " */\n"]
];
IF ~UseReferenceCounting[] THEN {
C2CEmit.AppendCode[moduleHeader, "/* ref-counting: off */\n"];
};
BEGIN
header: Rope.ROPE ¬ IO.PutFR["file: %g, module: %g", [rope[C2CAccess.params.fileName]], [rope[C2CAccess.params.moduleName]]];
C2CEmit.AppendCode[moduleHeader, C2CEmit.Cat[C2CEmit.CComment[header], "\n"]];
END;
FOR rl: LIST OF Rope.ROPE ¬ C2CAccess.params.commentLines, rl.rest WHILE rl#NIL DO
C2CEmit.AppendCode[moduleHeader, C2CEmit.Cat[C2CEmit.CComment[rl.first], "\n"]];
ENDLOOP;
C2CEmit.AppendCode[typeDeclarations, C2CTarget.definitions];
C2CRunTime.IncludeInstallationSupport[];
C2CRunTime.IncludeCedarExtra[];
maincc ¬ GenNode[node, skipMode];
IF maincc.ec#NIL THEN CantHappen;
WITH GetProp[myKeyForFirstProc] SELECT FROM
r: ROPE => firtProcName ¬ r;
ENDCASE => ERROR CantHappen;
moduleInitCode ¬ C2CEmit.Cat[
Rope.Cat["extern void ", C2CRunTime.install, "←", progName],
Rope.Concat["() {", C2CEmit.nestNLine],
C2CEmit.CollectCode[moduleInitializations],
Rope.Cat[C2CEmit.line, firtProcName, "();\n}", C2CEmit.unNestNLine],
];
C2CEmit.AppendCode[moduleContents, maincc.sc];
C2CEmit.AppendCode[moduleContents, moduleInitCode];
OuterInstallation[progName];
};
moduleHC, moduleDC, moduleDCP, typeDC, macroDC, procsC, userTypesC, globalFrameC: Code;
C2CPreprocessing.EliminateSideEffectsOfErrors[];
CountUsageOfStrings[];
GenMain[C2CBasics.rootNode];
BEGIN --version processing;
versionDeclC: Code;
prefix: ROPE ¬ Rope.Concat["@", "(#)"];--prevent finding string in compiler source itself
version: ROPE ¬ C2CAccess.params.versionStamp;
moduleName: ROPE ¬ C2CAccess.params.moduleName;
IF version#NIL
THEN {
versionVar: ROPE ¬ C2CNames.TryName["versionStamp"];
versionDeclC ¬ C2CEmit.Cat["static char ", versionVar, "[] = ", C2CCodeUtils.CString[IO.PutFR["%gmob←version %g %g", IO.rope[prefix], IO.rope[version], IO.rope[moduleName]]], ";\n"];
}
ELSE {
versionVar: ROPE ¬ C2CNames.TryName["c2cTime"];
versionDeclC ¬ C2CEmit.Cat["static char ", versionVar, "[] = ", C2CCodeUtils.CString[IO.PutFR["%gc2c←time [%g] %g", IO.rope[prefix], IO.time[], IO.rope[moduleName]]], ";\n"];
};
C2CEmit.AppendCode[moduleHeader, versionDeclC];
END;
moduleHC ¬ C2CEmit.CollectCode[moduleHeader, TRUE];
typeDC ¬ C2CEmit.CollectCode[typeDeclarations, TRUE];
macroDC ¬ C2CEmit.CollectCode[macroDeclarations, TRUE];
moduleDCP ¬ C2CEmit.CollectCode[moduleDeclarationsP, TRUE];
moduleDC ¬ C2CEmit.CollectCode[moduleDeclarations, TRUE];
procsC ¬ C2CEmit.CollectCode[moduleContents, TRUE];
userTypesC ¬ C2CEmit.CollectCode[userTypeDeclaration, TRUE];
globalFrameC ¬ C2CEmit.CollectCode[globalFrameDeclaration, TRUE];
code ¬ C2CEmit.Cat[moduleHC, C2CEmit.line, typeDC, C2CEmit.line];
code ¬ C2CEmit.Cat[code, macroDC, C2CEmit.line, moduleDCP, C2CEmit.line];
code ¬ C2CEmit.Cat[code, moduleDC, C2CEmit.line, globalFrameC, C2CEmit.line];
code ¬ C2CEmit.Cat[code, userTypesC, C2CEmit.line, procsC, C2CEmit.line];
C2CBasics.Report[];
};
OuterInstallation: PROC [progName: ROPE] = {
st: IO.STREAM ¬ IO.ROS[];
pre: ROPE ¬ C2CTarget.runtimePrefix;
gf: ROPE ¬ C2CGlobalFrame.GlobalFrameName[];
C: PROC [r1, r2, r3: ROPE¬NIL] = {
IO.PutRope[st, r1]; IO.PutRope[st, r2]; IO.PutRope[st, r3];
};
C["extern void ", pre, "run←"]; C[progName, "() { ", pre]; C["Start(&", gf, "); }\n"];
C2CEmit.AppendCode[moduleContents, C2CEmit.RopeCode[IO.RopeFromROS[st]]];
};

C2CBasics.CallbackWhenC2CIsCalled[ResetGlobalSmallConstantsTable];
C2CBasics.CallbackWhenC2CIsCalled[ResetSourceStuff];
END.