FoxIntermediateCode.Mod 45 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236
  1. MODULE FoxIntermediateCode; (** AUTHOR "fof"; PURPOSE "Oberon Compiler Abstract Intermediate Code"; *)
  2. (* Active Oberon Compiler, (c) 2009 Felix Friedrich *)
  3. IMPORT
  4. Sections := FoxSections, Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, BinaryCode := FoxBinaryCode, Backend := FoxBackend,
  5. SYSTEM, Streams, Global := FoxGlobal, D := Debugging, ObjectFile;
  6. CONST
  7. (* operand modes *)
  8. Undefined*=0;
  9. ModeRegister*=1; (* register operand *)
  10. ModeMemory*=2; (* memory operand, may be memory on register or immediate *)
  11. ModeImmediate*=3; (* immediate number with type, may include section implying a fixup of the immediate *)
  12. ModeNumber*=4; (* immediate integer number without any type, typically used as meta-information for instructions *)
  13. ModeString*=5; (* for inline code *)
  14. ModeRule*=6; (* for inline code with replacements *)
  15. (* operand classes *)
  16. Undef* = {Undefined};
  17. Imm*={ModeImmediate};
  18. Reg*={ModeRegister};
  19. RegMem* = {ModeRegister,ModeMemory};
  20. RegMemImm* = {ModeRegister,ModeMemory,ModeImmediate};
  21. UndefReg*={Undefined,ModeRegister};
  22. UndefRegMem*={Undefined, ModeRegister, ModeMemory};
  23. UndefRule*= {Undefined, ModeRule};
  24. Num* = {ModeNumber};
  25. Str*= {ModeString};
  26. Any = {Undefined, ModeRegister, ModeMemory, ModeImmediate};
  27. (* operand types *)
  28. SignedInteger* = 1;
  29. UnsignedInteger* = 2;
  30. Integer*= {SignedInteger,UnsignedInteger};
  31. Float* = 3;
  32. (* instruction format flags *)
  33. SameType12*=0; (* type of first operand must match type of second operand *)
  34. SameType23*=1; (* type of second operand must match type of third operand *)
  35. Op1IsDestination*=2; (* first operand is a destination operand (=>may not be register with offset) *)
  36. Commute23*=3; (* second and third operand can be exchanged *)
  37. SameSize12*=4;
  38. (* operand sizes in bits *)
  39. Bits8*=8; Bits16*=16; Bits32*=32; Bits64*=64; Bits128*=128;
  40. (* register classes *)
  41. GeneralPurpose*=0;
  42. Parameter*=1; (* *)
  43. (* special registers *)
  44. None*=-1; (* no register assigned *)
  45. SP*=-2; (* stack pointer *)
  46. FP*=-3; (* frame pointer *)
  47. AP*=-4; (* activity pointer *)
  48. HwRegister*=-32; (* any value below or equal hwreg is a user defined hardware register *)
  49. (* FoxProgTools.Enum -e -l=8
  50. nop mov conv call enter exit leave return result trap
  51. br breq brne brge brlt
  52. pop push neg not abs
  53. mul div mod sub add and or xor shl shr rol ror
  54. cas copy fill asm data reserve label special NofOpcodes~
  55. *)
  56. nop*= 0; mov*= 1; conv*= 2; call*= 3; enter*= 4; exit*= 5; leave*= 6; return*= 7;
  57. result*= 8; trap*= 9; br*= 10; breq*= 11; brne*= 12; brge*= 13; brlt*= 14; pop*= 15;
  58. push*= 16; neg*= 17; not*= 18; abs*= 19; mul*= 20; div*= 21; mod*= 22; sub*= 23;
  59. add*= 24; and*= 25; or*= 26; xor*= 27; shl*= 28; shr*= 29; rol*= 30; ror*= 31;
  60. cas*= 32; copy*= 33; fill*= 34; asm*= 35; data*= 36; reserve*= 37; label*= 38; special*= 39;
  61. NofOpcodes*= 40;
  62. NotYetCalculatedSize = -2;
  63. TYPE
  64. Type*=RECORD
  65. form-: SHORTINT; (* SignedInteger, UnsignedInteger or Float *)
  66. sizeInBits-: INTEGER; (* size in bits *)
  67. length-: LONGINT; (* vector length, if any. If zero then type is scalar *)
  68. END;
  69. RegisterClass*=RECORD
  70. class-: SHORTINT;
  71. number-: INTEGER;
  72. END;
  73. Rules*= POINTER TO ARRAY OF Operand;
  74. RegisterMap*= RECORD register*: LONGINT; name*: SyntaxTree.SourceCode END;
  75. BackendRules*= POINTER TO ARRAY OF RegisterMap;
  76. Operand* = RECORD
  77. mode-: SHORTINT; (* Undefined, ModeRegister, ModeImmediate, ModeMemory, ModeNumber or ModeString *)
  78. type-: Type; (* size and form *)
  79. register-: LONGINT; (* (virtual) register number, equals None if no register *)
  80. registerClass-: RegisterClass; (* normal register vs. special registers such as parameter registers *)
  81. offset-: LONGINT; (* offset on register or immediate symbol, in units *)
  82. intValue-: HUGEINT; (* integer value, if mode = ModeImmediate and type.form IN Integer or ModeNumber *)
  83. floatValue-: LONGREAL; (* real value, if mode = ModeImmediate and type.form = Float *)
  84. symbol-: ObjectFile.Identifier; (* referenced symbol, only valid for mode = ModeImmediate or mode = ModeMemory *)
  85. symbolOffset-: LONGINT; (* offset in IntermediateCode section, the difference to offset is that symbolOffset needs a resolving to real address offset *)
  86. resolved*: Sections.Section; (** only cache ! *)
  87. string-: SyntaxTree.SourceCode; (* string, if Mode = ModeString *)
  88. rule-: Rules;
  89. END;
  90. (*
  91. OperandMode Used Fields
  92. ModeRegister mode, type, register & offset
  93. ModeImmediate mode, type, intValue or floatValue or symbol & offset
  94. ModeMemory mode, type, register, offset, intValue or symbol & offset
  95. ModeNumber mode, intValue
  96. ModeString mode, string
  97. *)
  98. Instruction* = RECORD
  99. opcode-: SHORTINT; (* instruction opcode *)
  100. subtype-: SHORTINT; (* for special backend instruction *)
  101. textPosition-: LONGINT; (* for error handling and tracking (findPC) *)
  102. pc-: LONGINT; (* backend program counter (in bits) for debugging and for label fixups in backend *)
  103. op1*,op2*,op3*: Operand; (* first operand typically provides the result, if any *)
  104. END;
  105. InstructionFormat* = RECORD
  106. name-: ARRAY 16 OF CHAR; (* name, for assemby and disassembly *)
  107. op1-,op2-,op3-: SET; (* permitted modes for this kind of instruction *)
  108. flags-: SET; (* more flags determining restrictions (such as operand type matching etc.) *)
  109. END;
  110. Instructions*=POINTER TO ARRAY OF Instruction;
  111. (** code object *)
  112. Section*= OBJECT (Sections.Section)
  113. VAR
  114. instructions-: Instructions; (* array of instructions *)
  115. pc-: LONGINT; (* points to next instruction = len *)
  116. finally-: LONGINT; (* finally section starts at, -1 if none *)
  117. resolved-, alias-: BinaryCode.Section; (* reference to section containing compiled byte array *) (* TODO: ret rid of that? *)
  118. aliasOffset-: LONGINT; (* for aliases *)
  119. comments-: Sections.CommentWriter;
  120. validPAFEnter-,validPAFExit-: LONGINT; (* begin and end of code section where current PAF (procedure activation frame) is considered valid *)
  121. sizeInUnits: LONGINT;
  122. exported-: BOOLEAN;
  123. PROCEDURE GetPC(): LONGINT;
  124. BEGIN RETURN pc
  125. END GetPC;
  126. PROCEDURE & InitIntermediateSection*(type: SHORTINT; priority: INTEGER; CONST n: Basic.SegmentedName; symbol: SyntaxTree.Symbol; comment: BOOLEAN);
  127. BEGIN
  128. InitSection(type,priority,n,symbol); (*InitArray;*) pc := 0; resolved := NIL;
  129. IF comment THEN NEW(comments,GetPC) ELSE comments := NIL END;
  130. finally := -1;
  131. validPAFEnter := 0; validPAFExit := 0;
  132. sizeInUnits := NotYetCalculatedSize;
  133. exported := FALSE;
  134. END InitIntermediateSection;
  135. PROCEDURE SetExported*(e: BOOLEAN);
  136. BEGIN
  137. exported := e
  138. END SetExported;
  139. PROCEDURE EnableComments*(enabled: BOOLEAN);
  140. BEGIN
  141. IF enabled & (comments = NIL) THEN NEW(comments, GetPC)
  142. ELSIF ~enabled THEN comments := NIL
  143. END;
  144. END EnableComments;
  145. PROCEDURE EnterValidPAF*;
  146. BEGIN validPAFEnter := pc
  147. END EnterValidPAF;
  148. PROCEDURE ExitValidPAF*;
  149. BEGIN validPAFExit := pc
  150. END ExitValidPAF;
  151. PROCEDURE DeleteComments*;
  152. BEGIN comments := NIL
  153. END DeleteComments;
  154. PROCEDURE SetResolved*(section: BinaryCode.Section);
  155. BEGIN resolved := section
  156. END SetResolved;
  157. PROCEDURE SetAlias*(section: BinaryCode.Section; offset: LONGINT);
  158. BEGIN
  159. alias := section; aliasOffset := offset;
  160. END SetAlias;
  161. PROCEDURE SetFinally*(atPc: LONGINT);
  162. BEGIN finally := atPc
  163. END SetFinally;
  164. PROCEDURE GetSize*(): LONGINT;
  165. VAR
  166. i: LONGINT;
  167. instruction: Instruction;
  168. BEGIN
  169. IF sizeInUnits = NotYetCalculatedSize THEN
  170. sizeInUnits := Sections.UnknownSize; (* default value *)
  171. IF bitsPerUnit # Sections.UnknownSize THEN (* only calculate the size if the unit size is known *)
  172. IF (type = Sections.VarSection) OR (type = Sections.ConstSection) THEN
  173. sizeInUnits := 0;
  174. (* go through all instructions *)
  175. FOR i := 0 TO pc - 1 DO
  176. instruction := instructions[i];
  177. CASE instruction.opcode OF
  178. | data:
  179. (* TODO: correct? *)
  180. ASSERT((instruction.op1.mode = ModeImmediate) OR (instruction.op1.mode = ModeMemory));
  181. ASSERT((instruction.op1.type.sizeInBits MOD bitsPerUnit) = 0);
  182. INC(sizeInUnits, instruction.op1.type.sizeInBits DIV bitsPerUnit); (* TODO: correct conversion from bits to units? *)
  183. | reserve:
  184. ASSERT(instruction.op1.mode = ModeNumber);
  185. INC(sizeInUnits, LONGINT(instruction.op1.intValue))
  186. ELSE
  187. HALT(100); (* a var/const section may not contain any other type of instruction *)
  188. END
  189. END
  190. END
  191. END
  192. END;
  193. RETURN sizeInUnits
  194. END GetSize;
  195. PROCEDURE InitArray;
  196. CONST MinInstructions = 8;
  197. BEGIN
  198. IF instructions = NIL THEN NEW(instructions, MinInstructions); END;
  199. pc := 0;
  200. END InitArray;
  201. (* very useful for debugging:
  202. PROCEDURE Assert*(b: BOOLEAN; CONST s: ARRAY OF CHAR);
  203. BEGIN
  204. IF ~b THEN commentWriter.String("ASSERT FAILED: "); commentWriter.String(s); commentWriter.Ln END;
  205. END Assert;
  206. *)
  207. PROCEDURE Emit*(instruction: Instruction);
  208. VAR new: Instructions;
  209. op1size,op2size,op3size,op1form,op2form,op3form: LONGINT;
  210. i: SIZE;
  211. BEGIN
  212. op1size := instruction.op1.type.sizeInBits;
  213. op2size := instruction.op2.type.sizeInBits;
  214. op3size := instruction.op3.type.sizeInBits;
  215. op1form := instruction.op1.type.form;
  216. op2form := instruction.op2.type.form;
  217. op3form := instruction.op3.type.form;
  218. IF SameType12 IN instructionFormat[instruction.opcode].flags THEN
  219. Assert(TypeEquals(instruction.op1.type,instruction.op2.type),"operands 1 and 2 not of same type");
  220. END;
  221. IF SameSize12 IN instructionFormat[instruction.opcode].flags THEN
  222. Assert(instruction.op1.type.sizeInBits*instruction.op1.type.length = instruction.op2.type.sizeInBits*instruction.op2.type.length, "operands 1 and 2 not of same size");
  223. END;
  224. IF SameType23 IN instructionFormat[instruction.opcode].flags THEN
  225. Assert(TypeEquals(instruction.op2.type,instruction.op3.type),"operands 2 and 3 not of same type");
  226. END;
  227. IF Op1IsDestination IN instructionFormat[instruction.opcode].flags THEN
  228. Assert((instruction.op1.mode # ModeRegister) OR (instruction.op1.offset = 0),"destination operand may not be register with nonzero offset");
  229. END;
  230. Assert(instruction.op1.mode IN instructionFormat[instruction.opcode].op1,"invalid format of op 1");
  231. Assert(instruction.op2.mode IN instructionFormat[instruction.opcode].op2,"invalid format of op 2");
  232. Assert(instruction.op3.mode IN instructionFormat[instruction.opcode].op3,"invalid format of op 3");
  233. Assert(instruction.op1.symbol.name[0] # 0, "not intialized operand 1");
  234. Assert(instruction.op2.symbol.name[0] # 0, "not intialized operand 2");
  235. Assert(instruction.op3.symbol.name[0] # 0, "not intialized operand 3");
  236. IF (instructions = NIL) THEN
  237. NEW(instructions, 16);
  238. ELSIF pc = LEN(instructions) THEN
  239. NEW(new,4*LEN(instructions));
  240. FOR i := 0 TO LEN(instructions)-1 DO
  241. new[i] := instructions[i];
  242. END;
  243. instructions := new;
  244. END;
  245. instruction.pc := pc;
  246. instructions[pc] := instruction;
  247. INC(pc);
  248. sizeInUnits := NotYetCalculatedSize;
  249. END Emit;
  250. PROCEDURE EmitAt*(at: LONGINT; instruction: Instruction);
  251. VAR oldpc: LONGINT;
  252. BEGIN
  253. oldpc := pc;
  254. pc := at; Assert(pc < LEN(instructions),"EmitAt only in existing code");
  255. Emit(instruction);
  256. pc := oldpc;
  257. END EmitAt;
  258. PROCEDURE Reset*;
  259. BEGIN
  260. sizeInUnits := NotYetCalculatedSize;
  261. pc := 0;
  262. END Reset;
  263. PROCEDURE PatchOperands*(pc: LONGINT; op1,op2,op3: Operand);
  264. BEGIN instructions[pc].op1 := op1; instructions[pc].op2 := op2; instructions[pc].op3 := op3;
  265. END PatchOperands;
  266. PROCEDURE PatchAddress*(pc: LONGINT; symbolOffset: LONGINT);
  267. BEGIN
  268. ASSERT((br <= instructions[pc].opcode) & (instructions[pc].opcode <= brlt));
  269. ASSERT(instructions[pc].op1.symbol.name = SELF.name);
  270. (*
  271. ASSERT(instr[pc].op1.symbol = SELF);
  272. *)
  273. instructions[pc].op1.symbolOffset := symbolOffset;
  274. END PatchAddress;
  275. PROCEDURE SetPC*(at: LONGINT; pc: LONGINT);
  276. BEGIN instructions[at].pc := pc;
  277. END SetPC;
  278. PROCEDURE DumpCode*(w: Streams.Writer; from,to: LONGINT);
  279. VAR
  280. i: LONGINT;
  281. c: Sections.Comment;
  282. BEGIN
  283. IF comments # NIL THEN
  284. c := comments.firstComment;
  285. WHILE(c # NIL) & (c.pos <from) DO
  286. c := c.nextComment;
  287. END;
  288. i := from;
  289. WHILE(i<=to) DO
  290. IF (c # NIL) & (c.pos = i) THEN
  291. c.Dump(w); w.Ln;
  292. c := c.nextComment;
  293. END;
  294. w.Int(i,2); w.String(": ");
  295. DumpInstruction(w,instructions[i]);
  296. w.Ln;
  297. INC(i);
  298. END;
  299. IF (c#NIL) & (c.pos = to) THEN
  300. c.Dump(w); w.Ln;
  301. END;
  302. ELSE
  303. i := from;
  304. WHILE(i<=to) DO
  305. w.Int(i,2); w.String(": ");
  306. DumpInstruction(w,instructions[i]); w.Ln;
  307. INC(i);
  308. END;
  309. END;
  310. END DumpCode;
  311. (* inherited method *)
  312. PROCEDURE Dump(w: Streams.Writer);
  313. VAR ww: Basic.Writer;
  314. BEGIN
  315. IF resolved # NIL THEN
  316. Dump^(w);
  317. resolved.Dump(w)
  318. ELSE
  319. Dump^(w);
  320. ww := Basic.GetWriter(w);
  321. ww.IncIndent;
  322. ww.Ln;
  323. DumpCode(ww,0,pc-1);
  324. ww.DecIndent;
  325. END;
  326. END Dump;
  327. END Section;
  328. IntermediateBackend*= OBJECT (Backend.Backend)
  329. VAR
  330. runtimeModuleName-: SyntaxTree.IdentifierString;
  331. PROCEDURE SupportedInstruction*(CONST instr: Instruction; VAR moduleName,procedureName: ARRAY OF CHAR): BOOLEAN;
  332. BEGIN
  333. moduleName := ""; procedureName := "";
  334. RETURN TRUE
  335. END SupportedInstruction;
  336. PROCEDURE SetRuntimeModuleName*(CONST name: ARRAY OF CHAR);
  337. BEGIN
  338. COPY(name, runtimeModuleName);
  339. END SetRuntimeModuleName;
  340. END IntermediateBackend;
  341. VAR
  342. instructionFormat-: ARRAY NofOpcodes OF InstructionFormat;
  343. int8-, int16-, int32-, int64-, uint8-, uint16-, uint32-, uint64-, float32-, float64-, undef-: Type;
  344. GeneralPurposeRegister-: RegisterClass;
  345. empty: Operand;
  346. PROCEDURE Assert(condition: BOOLEAN; CONST reason: ARRAY OF CHAR);
  347. BEGIN (*ASSERT(condition);*) IF ~condition THEN D.TraceBack END;
  348. END Assert;
  349. (** create a new section in a given section list
  350. - if the section already exists, reuse the existing section
  351. note: for compatibility with the old binary object file format, const sections can also be referred to as var sections
  352. **)
  353. PROCEDURE NewSection*(list: Sections.SectionList; type: SHORTINT; CONST name: Basic.SegmentedName; syntaxTreeSymbol: SyntaxTree.Symbol; dump: BOOLEAN): Section;
  354. VAR
  355. t0: SHORTINT;
  356. result: Sections.Section;
  357. section: Section;
  358. BEGIN
  359. ASSERT(name[0] > 0); (* must be initialized *)
  360. IF syntaxTreeSymbol # NIL THEN
  361. result := list.FindBySymbol(syntaxTreeSymbol);
  362. END;
  363. (* search by name *)
  364. IF result = NIL THEN
  365. result := list.FindByName(name);
  366. END;
  367. IF result # NIL THEN
  368. section := result(Section);
  369. (*
  370. t0 := result.type;
  371. IF t0 # type THEN
  372. D.String("section entered twice: "); Basic.WriteSegmentedName(D.Log, name);
  373. D.String(" type "); D.Int(t0,1); D.String(" --> "); D.Int(type,1); D.Ln
  374. END;
  375. *)
  376. ASSERT(result.name= name);
  377. (*ASSERT(result.symbol = syntaxTreeSymbol);*)
  378. RETURN section
  379. END;
  380. (* a valid name must be present *)
  381. ASSERT(name[0] > 0);
  382. (* create a new section and enter it *)
  383. NEW(section, type, 0 (* initial priority = 0 *), name, syntaxTreeSymbol, dump);
  384. IF syntaxTreeSymbol # NIL THEN section.SetFingerprint(syntaxTreeSymbol.fingerprint.shallow) END;
  385. list.AddSection(section);
  386. RETURN section
  387. END NewSection;
  388. PROCEDURE SameOperand*(CONST left, right: Operand): BOOLEAN;
  389. VAR mode: LONGINT;
  390. BEGIN
  391. mode := left.mode;
  392. IF (left.type.form =right.type.form) & (left.type.sizeInBits=right.type.sizeInBits) & (left.type.length = right.type.length) & (mode = right.mode) THEN
  393. CASE mode OF
  394. ModeRegister: RETURN (left.register = right.register) & (left.offset = right.offset)
  395. |ModeMemory: RETURN (left.register = right.register) &(left.offset = right.offset) & (left.symbol = right.symbol) & (left.symbolOffset = right.symbolOffset);
  396. |ModeImmediate:
  397. IF left.type.form = Float THEN
  398. RETURN (left.floatValue = right.floatValue) & (left.symbol = right.symbol) & (left.symbolOffset = right.symbolOffset)
  399. ELSE
  400. RETURN (left.intValue = right.intValue) & (left.symbol = right.symbol) & (left.symbolOffset = right.symbolOffset)
  401. END;
  402. |ModeNumber:
  403. RETURN left.intValue = right.intValue
  404. |ModeString:
  405. RETURN left.string = right.string
  406. |Undefined: (* nothing *) RETURN TRUE
  407. END;
  408. ELSE RETURN FALSE
  409. END;
  410. END SameOperand;
  411. (** check if an operand is valid at a certain location for a given instruction opcode **)
  412. PROCEDURE CheckOperand*(operand: Operand; opCode, location: LONGINT; VAR message: ARRAY OF CHAR): BOOLEAN;
  413. VAR
  414. validOperandModes: SET;
  415. BEGIN
  416. validOperandModes := {};
  417. CASE location OF
  418. | 0: validOperandModes := instructionFormat[opCode].op1
  419. | 1: validOperandModes := instructionFormat[opCode].op2
  420. | 2: validOperandModes := instructionFormat[opCode].op3
  421. END;
  422. IF ~(operand.mode IN validOperandModes) THEN
  423. message := "operand mode mismatch"; RETURN FALSE
  424. END;
  425. (* the following code was taken from the previous version of 'PROCEDURE CheckOperand' and adapted: *)
  426. CASE operand.mode OF
  427. | Undefined:
  428. | ModeNumber:
  429. | ModeMemory:
  430. IF operand.type.form = Undefined THEN message := "memory type form undefined"; RETURN FALSE END;
  431. IF operand.type.sizeInBits = 0 THEN message :="memory type size undefined"; RETURN FALSE END;
  432. IF operand.register # None THEN
  433. IF operand.symbol.name # "" THEN message :="symbol and register cannot be both set in a memory operand"; RETURN FALSE END
  434. ELSIF operand.symbol.name # "" THEN
  435. IF operand.intValue # 0 THEN message :="memory operand on non zero immediate with symbol # NIL"; RETURN FALSE END
  436. (*ELSE
  437. IF operand.intValue = 0 THEN message :="memory operand on address 0 zero without register and symbol"; RETURN FALSE END
  438. *)
  439. END
  440. | ModeRegister:
  441. IF operand.type.form = Undefined THEN message :="register type form undefined"; RETURN FALSE END;
  442. IF operand.type.sizeInBits = 0 THEN message :="register type size undefined"; RETURN FALSE END;
  443. IF operand.register = None THEN message :="register undefined in register operand"; RETURN FALSE END
  444. | ModeImmediate:
  445. IF operand.symbol.name # "" THEN
  446. IF operand.intValue # 0 THEN message :="forbidden immediate with symbol and intValue # 0"; RETURN FALSE END;
  447. IF operand.floatValue # 0 THEN message :="forbidden immediate with symbol and floatValue # 0"; RETURN FALSE END
  448. END
  449. | ModeString:
  450. IF operand.string = NIL THEN message :="nil string in string operand"; RETURN FALSE END
  451. END;
  452. RETURN TRUE
  453. END CheckOperand;
  454. (** check if an instruction is valid **)
  455. PROCEDURE CheckInstruction*(instruction: Instruction; VAR message: ARRAY OF CHAR): BOOLEAN;
  456. BEGIN
  457. IF (SameType12 IN instructionFormat[instruction.opcode].flags) & ~TypeEquals(instruction.op1.type, instruction.op2.type) THEN
  458. message := "operands 1 and 2 not of same type";
  459. RETURN FALSE
  460. END;
  461. IF (SameSize12 IN instructionFormat[instruction.opcode].flags) & (instruction.op1.type.sizeInBits # instruction.op2.type.sizeInBits) THEN
  462. message := "operands 1 and 2 not of same size";
  463. RETURN FALSE
  464. END;
  465. IF (SameType23 IN instructionFormat[instruction.opcode].flags) & ~TypeEquals(instruction.op2.type, instruction.op3.type) THEN
  466. message := "operands 2 and 3 not of same type";
  467. RETURN FALSE
  468. END;
  469. IF (Op1IsDestination IN instructionFormat[instruction.opcode].flags) & (instruction.op1.mode = ModeRegister) & (instruction.op1.offset # 0) THEN
  470. message := "destination operand may not be register with nonzero offset";
  471. RETURN FALSE
  472. END;
  473. RETURN TRUE
  474. END CheckInstruction;
  475. PROCEDURE DumpRegister*(w: Streams.Writer; registerNumber: LONGINT; CONST registerClass: RegisterClass);
  476. BEGIN
  477. IF registerNumber = SP THEN
  478. w.String("sp")
  479. ELSIF registerNumber = FP THEN
  480. w.String("fp")
  481. ELSIF registerNumber = AP THEN
  482. w.String("ap")
  483. ELSIF registerNumber > None THEN
  484. w.String("r"); w.Int(registerNumber, 0);
  485. IF registerClass.class = Parameter THEN w.String(":p"); w.Int(registerClass.number,0) END;
  486. ELSIF registerNumber <= HwRegister THEN
  487. w.String("h"); w.Int(HwRegister - registerNumber, 0)
  488. ELSE
  489. w.String("(invalid register)")
  490. END
  491. END DumpRegister;
  492. PROCEDURE DumpType*(w: Streams.Writer; type: Type);
  493. BEGIN
  494. IF type.length > 1 THEN
  495. w.String("v"); w.Int(type.length,0);
  496. END;
  497. CASE type.form OF
  498. | Undefined: w.String("(invalid type)")
  499. | UnsignedInteger: w.String("u"); w.Int(type.sizeInBits, 0)
  500. | SignedInteger: w.String("s"); w.Int(type.sizeInBits, 0)
  501. | Float: w.String("f"); w.Int(type.sizeInBits, 0)
  502. END
  503. END DumpType;
  504. PROCEDURE DumpOperand*(w: Streams.Writer; CONST operand: Operand );
  505. VAR i: LONGINT;
  506. PROCEDURE DumpString(CONST str: ARRAY OF CHAR);
  507. VAR
  508. i: LONGINT;
  509. ch: CHAR;
  510. newln: BOOLEAN;
  511. BEGIN
  512. w.String('"');
  513. i := 0;
  514. ch := str[i];
  515. WHILE ch # 0X DO
  516. IF (ch = 0DX) OR (ch = 0AX) THEN
  517. newln := TRUE
  518. ELSE
  519. IF newln THEN
  520. w.Ln;
  521. newln := FALSE;
  522. END;
  523. IF (ch = '"') OR (ch = '\') THEN
  524. w.Char( '\' );
  525. w.Char(ch);
  526. ELSE
  527. w.Char(ch);
  528. END
  529. END;
  530. INC(i);
  531. ch := str[i];
  532. END;
  533. w.String('"');
  534. END DumpString;
  535. BEGIN
  536. IF operand.type.form # Undefined THEN
  537. DumpType(w,operand.type); w.String(" ");
  538. END;
  539. CASE operand.mode OF
  540. Undefined: w.String("!Undefined");
  541. |ModeMemory:
  542. w.String("[");
  543. IF operand.register # None THEN
  544. DumpRegister(w,operand.register, operand.registerClass);
  545. IF operand.offset > 0 THEN w.String("+"); w.Int(operand.offset,1);
  546. ELSIF operand.offset < 0 THEN w.String("-"); w.Int(-operand.offset,1);
  547. END;
  548. ELSIF operand.symbol.name # "" THEN
  549. Basic.WriteSegmentedName(w,operand.symbol.name);
  550. IF operand.symbol.fingerprint # 0 THEN w.String("["); w.Hex(operand.symbol.fingerprint,-8); w.String("]"); END;
  551. w.String(":"); w.Int(operand.symbolOffset,1);
  552. IF operand.offset > 0 THEN w.String("+"); w.Int(operand.offset, 1);
  553. ELSIF operand.offset < 0 THEN w.String("-"); w.Int(-operand.offset, 1);
  554. END;
  555. ELSE w.Int(SHORT(operand.intValue),1);
  556. END;
  557. w.String("]");
  558. |ModeRegister:
  559. DumpRegister(w,operand.register, operand.registerClass);
  560. IF operand.offset > 0 THEN w.String("+"); w.Int(operand.offset,1);
  561. ELSIF operand.offset < 0 THEN w.String("-"); w.Int(-operand.offset,1);
  562. END;
  563. |ModeImmediate:
  564. IF operand.symbol.name # "" THEN
  565. Basic.WriteSegmentedName(w,operand.symbol.name);
  566. IF operand.symbol.fingerprint # 0 THEN w.String("["); w.Hex(operand.symbol.fingerprint,-8); w.String("]"); END;
  567. w.String(":"); w.Int(operand.symbolOffset,1);
  568. IF operand.offset > 0 THEN w.String("+"); w.Int(operand.offset, 1);
  569. ELSIF operand.offset < 0 THEN w.String("-"); w.Int(-operand.offset, 1);
  570. END
  571. ELSE
  572. IF operand.type.form IN Integer THEN
  573. IF (operand.intValue > MAX(LONGINT)) OR (operand.intValue < MIN(LONGINT)) THEN
  574. w.String("0");
  575. w.Hex(operand.intValue,0);
  576. w.String("H");
  577. ELSE
  578. w.Int(SHORT(operand.intValue),1);
  579. END
  580. ELSE
  581. w.Float(operand.floatValue,24);
  582. END;
  583. END;
  584. |ModeString:
  585. DumpString(operand.string^);
  586. |ModeNumber: w.Int(SHORT(operand.intValue),1);
  587. |ModeRule:
  588. w.String("rules");
  589. FOR i := 0 TO LEN(operand.rule)-1 DO
  590. w.String(" "); DumpOperand(w,operand.rule[i]); w.String(" = "); DumpString(operand.rule[i].string^);
  591. END;
  592. END;
  593. (*
  594. w.Update();
  595. CheckOperand(operand);
  596. *)
  597. END DumpOperand;
  598. PROCEDURE TypeEquals*(CONST s1,s2: Type): BOOLEAN;
  599. BEGIN RETURN (s1.form = s2.form) & (s1.sizeInBits = s2.sizeInBits) & (s1.length = s2.length);
  600. END TypeEquals;
  601. PROCEDURE OperandEquals*(CONST s1,s2: Operand) : BOOLEAN;
  602. BEGIN
  603. RETURN (s1.mode = s2.mode) & (s1.register = s2.register) & (s1.offset = s2.offset) & (s1.intValue = s2.intValue) & (s1.floatValue = s2.floatValue)
  604. & (s1.symbol.name = s2.symbol.name) & (s1.string = s2.string) & (s1.symbolOffset = s2.symbolOffset) & TypeEquals(s1.type,s2.type);
  605. END OperandEquals;
  606. PROCEDURE Equals*(CONST i1, i2: Instruction):BOOLEAN;
  607. BEGIN
  608. IF i1.opcode # i2.opcode THEN RETURN FALSE END;
  609. IF i1.subtype # i2.subtype THEN RETURN FALSE END;
  610. IF i1.pc # i2.pc THEN RETURN FALSE END;
  611. IF ~OperandEquals(i1.op1, i2.op1) THEN RETURN FALSE END;
  612. IF ~OperandEquals(i1.op2, i2.op2) THEN RETURN FALSE END;
  613. IF ~OperandEquals(i1.op3, i2.op3) THEN RETURN FALSE END;
  614. RETURN TRUE
  615. END Equals;
  616. PROCEDURE DumpInstruction*(w: Streams.Writer; CONST instr: Instruction);
  617. BEGIN
  618. w.String(instructionFormat[instr.opcode].name);
  619. IF instr.op1.mode # Undefined THEN w.String(" "); DumpOperand(w,instr.op1) END;
  620. IF instr.op2.mode # Undefined THEN w.String(", "); DumpOperand(w,instr.op2) END;
  621. IF instr.op3.mode # Undefined THEN w.String(", "); DumpOperand(w,instr.op3) END;
  622. IF instr.opcode = special THEN w.String(" sub "); w.Int(instr.subtype,1) END;
  623. END DumpInstruction;
  624. PROCEDURE InitInstructions;
  625. PROCEDURE AddFormat(opcode: SHORTINT; CONST name: ARRAY OF CHAR; op1,op2,op3: SET; flags: SET);
  626. BEGIN
  627. COPY(name,instructionFormat[opcode].name);
  628. instructionFormat[opcode].op1 := op1;
  629. instructionFormat[opcode].op2 := op2;
  630. instructionFormat[opcode].op3 := op3;
  631. instructionFormat[opcode].flags := flags
  632. END AddFormat;
  633. BEGIN
  634. (* nop - no operation, may be used for optimisations *)
  635. AddFormat(nop, "nop", Undef, Undef, Undef, {});
  636. (* mov dest src - mov content of src to dest, if a third parameter is provided (set to a register),
  637. it has no meaning for interpreters or execution but provides a "reuse" hint for register allocators *)
  638. AddFormat(mov, "mov", RegMem, RegMemImm, UndefReg, {SameSize12,Op1IsDestination});
  639. (* conv dest src - convert src to dest, type of conversion derived from type of operands *)
  640. AddFormat(conv, "conv", RegMem, RegMemImm, Undef, {Op1IsDestination});
  641. (* call adr parSize - procedure call, second operand contains parameter size *)
  642. AddFormat(call, "call", RegMemImm, Num, Undef,{});
  643. (* enter cc pafSize regs - set up procedure activation frame; op1 = calling convention, op2 = paf size, op3 = numberOfParameters in registers *)
  644. AddFormat(enter, "enter", Num+Any, Num, Num ,{});
  645. (* leave cc - remove paf, does not imply return, op1= calling convention, does not imply exit from procedure *)
  646. AddFormat(leave, "leave", Num, Num, Undef ,{});
  647. (* return value : return value, op1= returned value, if any, does not imply exit from procedure *)
  648. AddFormat(return,"return",RegMemImm, Undef, Undef,{});
  649. (* exit parSize pcOffset cc - exit from procedure, op1 = offset that has to be subtracted from return address (e.g., used for ARM interrupt procedures), op2 = calling convention *)
  650. AddFormat(exit, "exit", Num, Num, Undef,{});
  651. (* result, store result to operand op1 *)
  652. AddFormat(result,"result",RegMem,Undef,Undef,{Op1IsDestination});
  653. (* trap num- interrupt*)
  654. AddFormat(trap, "trap", Num, Undef, Undef,{});
  655. (* br op1 - unconditional branch to op1 *)
  656. AddFormat(br, "br", RegMemImm, Undef, Undef,{});
  657. (* breq op1 op2 op3- branch to op1 if op2 = op3 *)
  658. AddFormat(breq, "breq", RegMemImm, RegMemImm, RegMemImm, {SameType23});
  659. (* brne op1 op2 op3 - branch to op2 if op2 # op3 *)
  660. AddFormat(brne, "brne", RegMemImm, RegMemImm, RegMemImm, {SameType23});
  661. (* brlt op1 op2 op3 - branch to op1 if op2 < op3 , information about sign is derived from operands *)
  662. AddFormat(brlt, "brlt", RegMemImm, RegMemImm, RegMemImm, {SameType23}); (* sign of comparison is derived from types of op1 and op2 *)
  663. (* brge op1 op2 op3 - branch to op1 if op2 >= op3 , information about sign is derived from operands *)
  664. AddFormat(brge, "brge", RegMemImm, RegMemImm, RegMemImm, {SameType23});
  665. (* pop op1 - pop op1 from stack *)
  666. AddFormat(pop, "pop", RegMem, Undef, Undef,{Op1IsDestination});
  667. (* push op1 - push op1 to stack *)
  668. AddFormat(push, "push", RegMemImm, Undef, Undef,{});
  669. (* not dest src - invert bit mask *)
  670. AddFormat(not, "not", RegMem, RegMemImm, Undef,{SameType12,Op1IsDestination});
  671. (* neg dest src - negate (arithmetic) *)
  672. AddFormat(neg, "neg", RegMem, RegMemImm, Undef,{SameType12,Op1IsDestination});
  673. (* abs dest src - absolute value (arithmetic) *)
  674. AddFormat(abs, "abs", RegMem, RegMemImm, Undef,{SameType12,Op1IsDestination});
  675. (* mul dest left right - multiply, information about sign and form (integer/float) in operands *)
  676. AddFormat(mul, "mul", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination,Commute23});
  677. (* div dest left right - divide, information about sign and form (integer/float) in operands *)
  678. AddFormat(div, "div", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination});
  679. (* mod dest left right - modulus, information about sign and form (integer/float) in operands *)
  680. AddFormat(mod, "mod", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination});
  681. (* sub dest left right - subtract, information about sign and form (integer/float) in operands *)
  682. AddFormat(sub, "sub", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination});
  683. (* add dest left right - add, information about sign and form (integer/float) in operands *)
  684. AddFormat(add, "add", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination,Commute23});
  685. (* and dest left right - bitwise and *)
  686. AddFormat(and, "and", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination,Commute23});
  687. (* or dest left right - bitwise or *)
  688. AddFormat(or, "or", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination,Commute23});
  689. (* xor dest left right - bitwise xor *)
  690. AddFormat(xor, "xor", RegMem, RegMemImm, RegMemImm,{SameType12,SameType23,Op1IsDestination,Commute23});
  691. (* shl dest left right - shift left (arithmetic or logical, derived from sign of operands) *)
  692. AddFormat(shl, "shl", RegMem, RegMemImm, RegMemImm,{SameType12,Op1IsDestination}); (* logical or arithemtic shift, derived from type of operands *)
  693. (* shr dest left right - shift right (arithmetic or logical, derived from sign of operands)*)
  694. AddFormat(shr, "shr", RegMem, RegMemImm, RegMemImm,{SameType12,Op1IsDestination});
  695. (* rol dest left right - rotate left *)
  696. AddFormat(rol, "rol", RegMem, RegMemImm, RegMemImm,{SameType12,Op1IsDestination});
  697. (* ror dest left right - rotate right *)
  698. AddFormat(ror, "ror", RegMem, RegMemImm, RegMemImm,{SameType12,Op1IsDestination});
  699. (* cas dest old new - compare value at dest with old and store new if equal, previous value in result register *)
  700. AddFormat(cas, "cas", RegMemImm, RegMemImm, RegMemImm,{SameType23});
  701. (* copy dest src size - move a block of size op3 units of memory from [op2] to [op1] *)
  702. AddFormat(copy, "copy", RegMemImm, RegMemImm, RegMemImm,{SameType12,SameType23});
  703. (* fill dest val size - fill a block of size op2 units of memory from [op1] with value in op3 *)
  704. AddFormat(fill, "fill", RegMemImm, RegMemImm, RegMemImm,{SameType12});
  705. (* asm attribute - asm code contained in attribute *)
  706. AddFormat(asm, "asm", Str, UndefRule, UndefRule,{});
  707. (* data imm - instruction to build up constants or (global) variables *)
  708. AddFormat(data, "data", Imm, Undef, Undef,{});
  709. (* reserve number - instruction to build (global) variables *)
  710. AddFormat(reserve, "reserve",Num,Undef,Undef,{});
  711. (* label - pseudo-instruction to reference back to source code positions *)
  712. AddFormat(label, "label",Num,Undef,Undef,{});
  713. (* special instruction support for backend addtions *)
  714. AddFormat(special,"special",Any, Any, Any, {} );
  715. END InitInstructions;
  716. PROCEDURE InitInstruction*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1,op2,op3: Operand);
  717. VAR format: InstructionFormat; mode1, mode2, mode3: LONGINT; (* debugging *)
  718. BEGIN
  719. format := instructionFormat[opcode];
  720. mode1 := op1.mode;
  721. mode2 := op2.mode;
  722. mode3 := op3.mode;
  723. (*
  724. Assert(op1.mode IN format.op1,"first operand mode mismatch");
  725. Assert(op2.mode IN format.op2,"second operand mode mismatch");
  726. Assert(op3.mode IN format.op3,"third operand mode mismatch");
  727. *)
  728. Assert(op1.symbol.name[0] # 0, "not intialized operand 1");
  729. Assert(op2.symbol.name[0] # 0, "not intialized operand 2");
  730. Assert(op3.symbol.name[0] # 0, "not intialized operand 3");
  731. instr.opcode := opcode;
  732. instr.op1 := op1;
  733. instr.op2 := op2;
  734. instr.op3 := op3;
  735. instr.textPosition := textPosition;
  736. END InitInstruction;
  737. PROCEDURE InitInstruction2*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1,op2: Operand);
  738. BEGIN
  739. InitInstruction(instr, textPosition, opcode, op1, op2, empty);
  740. END InitInstruction2;
  741. PROCEDURE InitInstruction1*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT; op1: Operand);
  742. BEGIN
  743. InitInstruction(instr, textPosition, opcode, op1, empty, empty);
  744. END InitInstruction1;
  745. PROCEDURE InitInstruction0*(VAR instr: Instruction; textPosition: LONGINT; opcode: SHORTINT);
  746. BEGIN
  747. InitInstruction(instr, textPosition, opcode, empty, empty, empty);
  748. END InitInstruction0;
  749. PROCEDURE SetSubType*(VAR instr: Instruction; subType: SHORTINT);
  750. BEGIN
  751. instr.subtype := subType
  752. END SetSubType;
  753. PROCEDURE InitOperand*(VAR op: Operand);
  754. BEGIN
  755. op.mode := Undefined;
  756. op.type.form := Undefined; op.type.sizeInBits := Undefined; op.type.length := 1;
  757. op.register := None; op.offset := 0; op.registerClass := GeneralPurposeRegister;
  758. op.intValue := 0;
  759. op.floatValue := 0;
  760. op.symbol.name := "";
  761. op.symbol.fingerprint := 0;
  762. op.symbolOffset := 0;
  763. END InitOperand;
  764. PROCEDURE InitRegister*(VAR op: Operand; type: Type; registerClass: RegisterClass; register: LONGINT);
  765. BEGIN
  766. Assert((register >0) OR (register = SP) OR (register = FP) OR (register = AP) OR (register <= HwRegister) ,"unmapped register number");
  767. InitOperand(op);
  768. op.mode := ModeRegister;
  769. op.type := type;
  770. op.registerClass := registerClass;
  771. op.register := register;
  772. END InitRegister;
  773. PROCEDURE Register*(type: Type; registerClass: RegisterClass; register: LONGINT): Operand;
  774. VAR op: Operand;
  775. BEGIN InitRegister(op,type,registerClass, register); RETURN op
  776. END Register;
  777. PROCEDURE RegisterOffset*(type: Type; registerClass: RegisterClass; register, offset: LONGINT): Operand;
  778. VAR op: Operand;
  779. BEGIN InitRegister(op,type,registerClass, register); SetOffset (op, offset); RETURN op
  780. END RegisterOffset;
  781. PROCEDURE AddOffset*(VAR op: Operand; offset: LONGINT);
  782. BEGIN
  783. Assert((op.mode = ModeRegister) OR (op.mode = ModeMemory) OR (op.mode = ModeImmediate) & (op.type.form IN {SignedInteger, UnsignedInteger}),"offset not on register or integer immediate");
  784. IF (op.mode = ModeImmediate) & (op.symbol.name = "") THEN
  785. INC(op.intValue,offset)
  786. ELSE
  787. INC(op.offset,offset)
  788. END
  789. END AddOffset;
  790. PROCEDURE SetOffset*(VAR op: Operand; offset: LONGINT);
  791. BEGIN
  792. Assert((op.mode = ModeRegister) OR (op.mode = ModeImmediate) & (op.type.form IN {SignedInteger, UnsignedInteger}),"offset not on register or integer immediate");
  793. op.offset := offset
  794. END SetOffset;
  795. PROCEDURE SetSymbol*(VAR op: Operand; symbol: Sections.SectionName; fp: LONGINT);
  796. BEGIN
  797. op.symbol.name := symbol;
  798. op.symbol.fingerprint := fp;
  799. END SetSymbol;
  800. PROCEDURE SetIntValue*(VAR op: Operand; intValue: HUGEINT);
  801. BEGIN op.intValue := intValue
  802. END SetIntValue;
  803. PROCEDURE MakeMemory*(VAR op: Operand; type: Type);
  804. BEGIN
  805. Assert((op.mode = ModeRegister) & (op.type.length < 2) OR (op.mode = ModeMemory) OR (op.mode = ModeImmediate) & (op.type.form = UnsignedInteger) ,"operand mode not of register or unsigned integer immediate");
  806. op.type := type;
  807. op.mode := ModeMemory;
  808. ASSERT(op.register # 0);
  809. END MakeMemory;
  810. PROCEDURE MakeAddress*(VAR op: Operand; CONST type: Type);
  811. BEGIN
  812. ASSERT(op.mode = ModeMemory);
  813. IF op.register = None THEN
  814. op.mode := ModeImmediate;
  815. ELSE
  816. op.mode := ModeRegister;
  817. ASSERT(op.symbol.name = "");
  818. END;
  819. op.type := type;
  820. END MakeAddress;
  821. PROCEDURE InitAddress*(VAR op: Operand; type: Type; symbol: Sections.SectionName; fp: LONGINT; symbolOffset: LONGINT);
  822. BEGIN
  823. Assert(symbol # "","forbidden nil symbol");
  824. ASSERT(symbol[0] # 0); (* not initialized *)
  825. InitImmediate(op,type,0); op.symbol.name := symbol; op.symbol.fingerprint := fp; op.type := type; op.symbolOffset := symbolOffset
  826. END InitAddress;
  827. PROCEDURE Address*(type: Type; symbol: Sections.SectionName; fp: LONGINT; offset: LONGINT): Operand;
  828. VAR op: Operand;
  829. BEGIN InitAddress(op,type,symbol,fp, offset); RETURN op
  830. END Address;
  831. PROCEDURE InitMemory*(VAR op:Operand; type: Type; base: Operand; offset: LONGINT);
  832. BEGIN
  833. Assert((base.mode = ModeRegister) OR (base.mode = ModeImmediate) & ((offset=0) OR (base.symbol.name#"")),"base operand must be register");
  834. op := base; INC(op.offset,offset); MakeMemory(op,type);
  835. END InitMemory;
  836. PROCEDURE Memory*(type: Type; base: Operand; offset: LONGINT): Operand;
  837. VAR op: Operand;
  838. BEGIN InitMemory(op,type,base,offset); RETURN op
  839. END Memory;
  840. PROCEDURE IsConstantInteger*(CONST op: Operand; VAR value: HUGEINT): BOOLEAN;
  841. BEGIN
  842. IF (op.mode = ModeImmediate) & (op.type.form IN Integer) & (op.symbol.name = "") THEN
  843. value := op.intValue;
  844. RETURN TRUE
  845. ELSE
  846. RETURN FALSE
  847. END;
  848. END IsConstantInteger;
  849. PROCEDURE InitImmediate*(VAR op: Operand; type: Type; value: HUGEINT);
  850. BEGIN
  851. Assert(type.form IN Integer,"operand type does not match value type");
  852. InitOperand(op); op.mode := ModeImmediate; op.type := type; op.intValue := value;
  853. END InitImmediate;
  854. PROCEDURE Immediate*(type: Type; value: LONGINT): Operand;
  855. VAR op: Operand;
  856. BEGIN InitImmediate(op,type,value); RETURN op
  857. END Immediate;
  858. PROCEDURE InitFloatImmediate*(VAR op: Operand; type: Type; value: LONGREAL);
  859. BEGIN
  860. Assert(type.form = Float,"operand type does not match value type");
  861. InitOperand(op); op.mode := ModeImmediate; op.type := type; op.floatValue := value;
  862. END InitFloatImmediate;
  863. PROCEDURE FloatImmediate*(type: Type; value: LONGREAL): Operand;
  864. VAR op: Operand;
  865. BEGIN InitFloatImmediate(op,type,value); RETURN op
  866. END FloatImmediate;
  867. PROCEDURE InitNumber*(VAR op: Operand; value: HUGEINT);
  868. BEGIN InitOperand(op); op.mode := ModeNumber; op.intValue := value;
  869. END InitNumber;
  870. PROCEDURE Number*(value: HUGEINT): Operand;
  871. VAR op: Operand;
  872. BEGIN InitNumber(op,value); RETURN op
  873. END Number;
  874. PROCEDURE InitRule*(VAR op: Operand; rules: Rules);
  875. BEGIN
  876. InitOperand(op); op.mode := ModeRule; op.rule := rules
  877. END InitRule;
  878. PROCEDURE InitString*(VAR op: Operand; string: SyntaxTree.SourceCode);
  879. BEGIN InitOperand(op); op.mode := ModeString; op.string := string;
  880. END InitString;
  881. PROCEDURE SetString*(VAR op: Operand; string: POINTER TO ARRAY OF CHAR);
  882. BEGIN op.string := string
  883. END SetString;
  884. PROCEDURE String*(string: SyntaxTree.SourceCode): Operand;
  885. VAR op: Operand;
  886. BEGIN InitString(op,string); RETURN op
  887. END String;
  888. PROCEDURE InitType*(VAR type: Type; form: SHORTINT; sizeInBits: INTEGER);
  889. BEGIN type.form := form; type.sizeInBits := sizeInBits; type.length := 1;
  890. END InitType;
  891. PROCEDURE ToVectorType*(VAR type: Type; length: LONGINT);
  892. BEGIN type.length := length
  893. END ToVectorType;
  894. PROCEDURE InitRegisterClass*(VAR registerClass: RegisterClass; class: SHORTINT; number: INTEGER);
  895. BEGIN registerClass.class := class; registerClass.number := number
  896. END InitRegisterClass;
  897. PROCEDURE NewType*(form: SHORTINT; sizeInBits: INTEGER): Type;
  898. VAR type: Type;
  899. BEGIN InitType(type, form, sizeInBits); RETURN type
  900. END NewType;
  901. PROCEDURE SetType*(VAR op: Operand; CONST type: Type);
  902. BEGIN op.type := type
  903. END SetType;
  904. (** assembler related part *)
  905. PROCEDURE FindMnemonic*(CONST name: ARRAY OF CHAR): SHORTINT;
  906. VAR i: SHORTINT;
  907. BEGIN
  908. FOR i := 0 TO NofOpcodes-1 DO
  909. IF name = instructionFormat[i].name THEN
  910. RETURN i
  911. END;
  912. END;
  913. RETURN None;
  914. END FindMnemonic;
  915. PROCEDURE SetRegister*(VAR op: Operand; reg: LONGINT);
  916. BEGIN
  917. op.register := reg; ASSERT(reg # 0);
  918. END SetRegister;
  919. PROCEDURE DecimalNumber(ch: CHAR; VAR nr: LONGINT): BOOLEAN;
  920. BEGIN
  921. IF (ch < "0") OR (ch > "9") THEN RETURN FALSE
  922. ELSE
  923. nr := nr *10;
  924. INC(nr,ORD(ch)-ORD("0"));
  925. RETURN TRUE
  926. END;
  927. END DecimalNumber;
  928. PROCEDURE Numbers(CONST name: ARRAY OF CHAR; VAR pos: LONGINT; VAR number: LONGINT): BOOLEAN;
  929. BEGIN
  930. number := 0;
  931. IF DecimalNumber(name[pos], number) THEN
  932. INC(pos);
  933. WHILE (pos<LEN(name)) & DecimalNumber(name[pos], number) DO INC(pos) END;
  934. RETURN TRUE
  935. ELSE
  936. RETURN FALSE
  937. END;
  938. END Numbers;
  939. PROCEDURE Character(CONST name: ARRAY OF CHAR; VAR pos: LONGINT; char: CHAR): BOOLEAN;
  940. BEGIN
  941. IF name[pos] = char THEN INC(pos); RETURN TRUE ELSE RETURN FALSE END;
  942. END Character;
  943. PROCEDURE DenotesRegister*(CONST name: ARRAY OF CHAR; VAR registerClass: RegisterClass; VAR register: LONGINT): BOOLEAN;
  944. VAR pos, registerNumber: LONGINT;
  945. BEGIN
  946. pos := 0;
  947. IF Character(name,pos,'r') THEN
  948. IF Numbers(name,pos,register) THEN
  949. IF Character(name,pos,0X) THEN registerClass := GeneralPurposeRegister; RETURN TRUE
  950. ELSIF Character(name,pos,':') & Character(name,pos,'p') & Numbers(name,pos,registerNumber) & Character(name,pos,0X) THEN
  951. InitRegisterClass(registerClass, Parameter, SHORT(registerNumber));
  952. RETURN TRUE
  953. END
  954. END;
  955. ELSIF Character(name,pos,'h') THEN
  956. IF Numbers(name,pos,register) & Character(name,pos,0X) THEN
  957. register := HwRegister - register; RETURN TRUE
  958. END;
  959. ELSIF name = "sp" THEN register := SP; RETURN TRUE
  960. ELSIF name = "fp" THEN register := FP ; RETURN TRUE
  961. ELSIF name = "ap" THEN register := AP ; RETURN TRUE
  962. ELSE RETURN FALSE
  963. END;
  964. END DenotesRegister;
  965. PROCEDURE UnsignedIntegerType*(bits: LONGINT): Type;
  966. BEGIN
  967. IF bits = 8 THEN RETURN uint8
  968. ELSIF bits=16 THEN RETURN uint16
  969. ELSIF bits=32 THEN RETURN uint32
  970. ELSIF bits=64 THEN RETURN uint64
  971. ELSE RETURN NewType(UnsignedInteger, SHORTINT(bits))
  972. END;
  973. END UnsignedIntegerType;
  974. PROCEDURE SignedIntegerType*(bits: LONGINT): Type;
  975. BEGIN
  976. IF bits = 8 THEN RETURN int8
  977. ELSIF bits=16 THEN RETURN int16
  978. ELSIF bits=32 THEN RETURN int32
  979. ELSIF bits=64 THEN RETURN int64
  980. ELSE RETURN NewType(SignedInteger, SHORTINT(bits))
  981. END;
  982. END SignedIntegerType;
  983. PROCEDURE FloatType*(bits: LONGINT): Type;
  984. BEGIN
  985. IF bits=32 THEN RETURN float32
  986. ELSIF bits=64 THEN RETURN float64
  987. ELSE RETURN NewType(Float, SHORTINT(bits))
  988. END;
  989. END FloatType;
  990. (** make an integer operand unsigned
  991. - note that no conversion is done, but only the type is changed **)
  992. PROCEDURE ToUnsigned*(operand: Operand): Operand;
  993. VAR
  994. type: Type;
  995. result: Operand;
  996. BEGIN
  997. ASSERT(operand.type.form IN Integer);
  998. result := operand;
  999. result.type.form := UnsignedInteger;
  1000. RETURN result
  1001. END ToUnsigned;
  1002. PROCEDURE DenotesType*(CONST name: ARRAY OF CHAR; VAR type: Type): BOOLEAN;
  1003. VAR
  1004. sizeInBits: LONGINT; pos: LONGINT;
  1005. BEGIN
  1006. pos := 0;
  1007. IF Character(name,pos,'s') THEN
  1008. IF Numbers(name, pos, sizeInBits) & Character(name,pos,0X) & (sizeInBits >0) THEN
  1009. type := SignedIntegerType(sizeInBits); RETURN TRUE
  1010. END;
  1011. ELSIF Character(name,pos,'u') THEN
  1012. IF Numbers(name, pos, sizeInBits) & Character(name,pos,0X) & (sizeInBits >0) THEN
  1013. type := UnsignedIntegerType(sizeInBits); RETURN TRUE
  1014. END;
  1015. ELSIF Character(name,pos, 'f') THEN
  1016. IF Numbers(name, pos, sizeInBits) & Character(name,pos,0X) & (sizeInBits >0) THEN
  1017. type := FloatType(sizeInBits); RETURN TRUE
  1018. END;
  1019. ELSE RETURN FALSE
  1020. END;
  1021. END DenotesType;
  1022. PROCEDURE GetType*(system: Global.System; type: SyntaxTree.Type): Type;
  1023. VAR t: Type;
  1024. BEGIN
  1025. type := type.resolved;
  1026. IF type IS SyntaxTree.CharacterType THEN
  1027. RETURN UnsignedIntegerType(system.SizeOf(type))
  1028. ELSIF type IS SyntaxTree.IntegerType THEN
  1029. IF type(SyntaxTree.IntegerType).signed THEN
  1030. RETURN SignedIntegerType(system.SizeOf(type))
  1031. ELSE
  1032. RETURN UnsignedIntegerType(system.SizeOf(type))
  1033. END;
  1034. ELSIF type IS SyntaxTree.FloatType THEN
  1035. RETURN FloatType(system.SizeOf(type))
  1036. ELSIF type IS SyntaxTree.RangeType THEN
  1037. RETURN GetType(system,system.addressType)
  1038. ELSIF type IS SyntaxTree.BasicType THEN
  1039. IF type IS SyntaxTree.SizeType THEN
  1040. RETURN SignedIntegerType(system.SizeOf(type))
  1041. ELSE
  1042. RETURN UnsignedIntegerType(system.SizeOf(type))
  1043. END;
  1044. ELSIF type IS SyntaxTree.PointerType THEN
  1045. RETURN GetType(system,system.addressType)
  1046. ELSIF type IS SyntaxTree.EnumerationType THEN
  1047. RETURN int32
  1048. ELSIF type IS SyntaxTree.ProcedureType THEN
  1049. RETURN GetType(system,system.addressType)
  1050. ELSIF type IS SyntaxTree.MathArrayType THEN
  1051. WITH type: SyntaxTree.MathArrayType DO
  1052. IF type.form = SyntaxTree.Static THEN
  1053. t := GetType(system, type.arrayBase);
  1054. ASSERT(t.length = 1);
  1055. ToVectorType(t, type.staticLength);
  1056. RETURN t
  1057. END;
  1058. END;
  1059. (* TODO: ok to comment out the following assertion?:
  1060. ASSERT(type(SyntaxTree.MathArrayType).form IN {SyntaxTree.Static, SyntaxTree.Tensor}); *)
  1061. RETURN GetType(system,system.addressType);
  1062. ELSIF (type IS SyntaxTree.ArrayType) & (type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) THEN
  1063. RETURN GetType(system,system.addressType);
  1064. ELSIF type IS SyntaxTree.PortType THEN
  1065. RETURN GetType(system, system.addressType);
  1066. ELSIF type IS SyntaxTree.CellType THEN
  1067. RETURN GetType(system, system.addressType);
  1068. ELSE
  1069. HALT(100);
  1070. END;
  1071. END GetType;
  1072. BEGIN
  1073. InitInstructions;
  1074. InitType(int8, SignedInteger,8);
  1075. InitType(int16, SignedInteger,16);
  1076. InitType(int32, SignedInteger,32);
  1077. InitType(int64, SignedInteger,64);
  1078. InitType(uint8, UnsignedInteger,8);
  1079. InitType(uint16, UnsignedInteger,16);
  1080. InitType(uint32, UnsignedInteger,32);
  1081. InitType(uint64, UnsignedInteger,64);
  1082. InitType(float32, Float,32);
  1083. InitType(float64, Float,64);
  1084. InitType(undef, Undefined,0);
  1085. InitOperand(empty);
  1086. END FoxIntermediateCode.