FoxIntermediateCode.Mod 45 KB

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