FoxMinosObjectFile.Mod 20 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564
  1. MODULE FoxMinosObjectFile; (** AUTHOR "fof"; PURPOSE "Oberon Compiler Minos Object File Writer"; *)
  2. IMPORT
  3. Scanner := FoxScanner, Basic := FoxBasic, SyntaxTree := FoxSyntaxTree, Global := FoxGlobal, SemanticChecker := FoxSemanticChecker, Fingerprinter := FoxFingerprinter, Sections := FoxSections,
  4. Streams, D := Debugging, Files, SYSTEM,Strings, BinaryCode := FoxBinaryCode, KernelLog, Diagnostics, SymbolFileFormat := FoxTextualSymbolFile, Options,
  5. Formats := FoxFormats, IntermediateCode := FoxIntermediateCode, Machine
  6. ;
  7. CONST
  8. Trace=FALSE;
  9. TYPE Name=ARRAY 256 OF CHAR;
  10. ByteArray = POINTER TO ARRAY OF CHAR;
  11. TYPE
  12. Fixup = OBJECT
  13. VAR
  14. nextFixup: Fixup;
  15. fixup: BinaryCode.Fixup;
  16. fixupSection: Sections.Section;
  17. END Fixup;
  18. ObjectFileFormat*= OBJECT (Formats.ObjectFileFormat)
  19. VAR extension,prefix: Basic.FileName;
  20. PROCEDURE Export*(module: Formats.GeneratedModule; symbolFileFormat: Formats.SymbolFileFormat): BOOLEAN;
  21. VAR symbolFile: Files.File; moduleName: SyntaxTree.IdentifierString; fileName: Files.FileName; f: Files.File; w: Files.Writer;
  22. VAR varSize, codeSize: LONGINT; VAR code: ByteArray; bodyOffset: LONGINT; error: BOOLEAN;
  23. BEGIN
  24. Global.ModuleFileName(module.module.name,module.module.context,moduleName);
  25. Basic.Concat(fileName,prefix,moduleName,extension);
  26. IF Trace THEN D.Str("FoxMinosObjectFile.ObjectFileFormat.Export "); D.Str(moduleName); D.Ln; END;
  27. IF ~(module IS Sections.Module) THEN
  28. Basic.Error(diagnostics, module.module.sourceName, Basic.invalidPosition, "generated module format does not match object file format");
  29. RETURN FALSE;
  30. ELSIF module.findPC # MAX(LONGINT) THEN
  31. MakeSectionOffsets(module(Sections.Module),varSize, codeSize, bodyOffset, code);
  32. RETURN FindPC(module.findPC,module(Sections.Module),diagnostics);
  33. ELSE
  34. WITH module: Sections.Module DO
  35. f := Files.New(fileName);
  36. ASSERT(f # NIL);
  37. NEW(w,f,0);
  38. error := ~WriteObjectFile(w,module,symbolFile, diagnostics);
  39. w.Update;
  40. Files.Register(f);
  41. RETURN ~error
  42. END;
  43. END;
  44. END Export;
  45. PROCEDURE DefineOptions*(options: Options.Options);
  46. BEGIN
  47. options.Add(0X,"objectFileExtension",Options.String);
  48. options.Add(0X,"objectFilePrefix",Options.String);
  49. END DefineOptions;
  50. PROCEDURE GetOptions*(options: Options.Options);
  51. BEGIN
  52. IF ~options.GetString("objectFileExtension",extension) THEN
  53. extension := ".arm"
  54. END;
  55. IF ~options.GetString("objectFilePrefix",prefix) THEN prefix := "" END
  56. END GetOptions;
  57. PROCEDURE DefaultSymbolFileFormat*(): Formats.SymbolFileFormat;
  58. BEGIN RETURN SymbolFileFormat.Get();
  59. END DefaultSymbolFileFormat;
  60. PROCEDURE ForceModuleBodies*(): BOOLEAN; (* necessary in binary object file format as bodies not recognizable later on *)
  61. BEGIN RETURN TRUE
  62. END ForceModuleBodies;
  63. PROCEDURE GetExtension*(VAR ext: ARRAY OF CHAR);
  64. BEGIN COPY(extension, ext)
  65. END GetExtension;
  66. END ObjectFileFormat;
  67. (*
  68. this procedure converts the section-based representation of fixups into a symbol based representation
  69. *)
  70. PROCEDURE GetFixups(diagnostics: Diagnostics.Diagnostics; module: Sections.Module; symbol: Sections.Section; VAR first: Fixup): LONGINT;
  71. VAR temp: Fixup; fixup: BinaryCode.Fixup; nr :LONGINT; i: LONGINT; section: Sections.Section; sectionList: Sections.SectionList;
  72. PROCEDURE Do;
  73. BEGIN
  74. FOR i := 0 TO sectionList.Length() - 1 DO
  75. section := sectionList.GetSection(i);
  76. IF (section.type # Sections.InlineCodeSection) & (section.type # Sections.InitCodeSection) THEN
  77. IF section(IntermediateCode.Section).resolved # NIL THEN
  78. fixup := section(IntermediateCode.Section).resolved.fixupList.firstFixup;
  79. WHILE (fixup # NIL) DO
  80. IF (fixup.symbol.name = symbol.name) THEN
  81. INC(nr);
  82. NEW(temp);
  83. temp.fixup := fixup;
  84. temp.fixupSection := section;
  85. temp.nextFixup := first;
  86. IF fixup.displacement # 0 THEN
  87. Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "Fixups with displacement # 0 not supported in Minos Object File.");
  88. END;
  89. first := temp;
  90. END;
  91. fixup := fixup.nextFixup;
  92. END;
  93. END
  94. END
  95. END;
  96. END Do;
  97. BEGIN
  98. first := NIL; nr := 0;
  99. sectionList := module.allSections; Do;
  100. sectionList := module.importedSections; Do;
  101. RETURN nr
  102. END GetFixups;
  103. PROCEDURE FindPC(pc: LONGINT; module: Sections.Module; diagnostics: Diagnostics.Diagnostics): BOOLEAN;
  104. VAR
  105. section:Sections.Section; binarySection: BinaryCode.Section; label: BinaryCode.LabelList;
  106. i: LONGINT;
  107. BEGIN
  108. FOR i := 0 TO module.allSections.Length() - 1 DO
  109. section := module.allSections.GetSection(i);
  110. binarySection := section(IntermediateCode.Section).resolved;
  111. IF ((section.offset ) <= pc) & (pc < (section.offset +binarySection.pc )) THEN
  112. label := binarySection.labels;
  113. WHILE (label # NIL) & ((label.offset + section.offset ) > pc) DO
  114. label := label.prev;
  115. END;
  116. IF label # NIL THEN
  117. Basic.Information(diagnostics, module.module.sourceName,label.position," pc position");
  118. RETURN TRUE
  119. END;
  120. END
  121. END;
  122. Basic.Error(diagnostics, module.module.sourceName,Basic.invalidPosition, " could not locate pc");
  123. RETURN FALSE
  124. END FindPC;
  125. PROCEDURE MakeSectionOffsets(module: Sections.Module; VAR varSize, codeSize, bodyOffset: LONGINT; VAR code: ByteArray);
  126. VAR symbolName: SyntaxTree.IdentifierString; symbol: SyntaxTree.Symbol; binarySection: BinaryCode.Section;
  127. PROCEDURE Copy(section: BinaryCode.Section; to: ByteArray; offset: LONGINT);
  128. VAR i,ofs: LONGINT;
  129. BEGIN
  130. ofs := (offset );
  131. FOR i := 0 TO ((section.pc-1) ) DO
  132. to[i+ofs] := CHR(section.os.bits.GetBits(i*8,8));
  133. END;
  134. END Copy;
  135. (*
  136. PROCEDURE ReportSection(section: Sections.Section);
  137. BEGIN
  138. D.String("Section "); Basic.WriteSegmentedName(D.Log, section.name); D.String(" allocated at "); D.Int(section.offset,1); D.Ln;
  139. END ReportSection;
  140. *)
  141. (*
  142. not necessary
  143. *)
  144. (* link body as first section: entry[0] = 0 *)
  145. PROCEDURE FirstOffsets(sectionList: Sections.SectionList);
  146. VAR
  147. section: Sections.Section;
  148. i: LONGINT;
  149. BEGIN
  150. FOR i := 0 TO sectionList.Length() - 1 DO
  151. section := sectionList.GetSection(i);
  152. binarySection := section(IntermediateCode.Section).resolved;
  153. symbol := section.symbol;
  154. IF symbol # NIL THEN
  155. symbol.GetName(symbolName);
  156. IF section.symbol = module.module.moduleScope.bodyProcedure THEN
  157. section.SetOffset(0); INC(codeSize,binarySection.pc);
  158. (*ReportSection(section)*)
  159. END;
  160. END
  161. END;
  162. END FirstOffsets;
  163. (* note: if 'caseSections' is TRUE, only case table sections are processed, otherwise only regular sections (imported symbol/system call sections are never processed) *)
  164. PROCEDURE SetOffsets(sectionList: Sections.SectionList);
  165. VAR
  166. section: Sections.Section;
  167. i: LONGINT;
  168. BEGIN
  169. FOR i := 0 TO sectionList.Length() - 1 DO
  170. section := sectionList.GetSection(i);
  171. binarySection := section(IntermediateCode.Section).resolved;
  172. symbol := section.symbol;
  173. IF symbol # NIL THEN
  174. symbol.GetName(symbolName);
  175. ELSE symbolName := "";
  176. END;
  177. IF section.symbol = module.module.moduleScope.bodyProcedure THEN
  178. ELSIF symbolName = "@moduleSelf" THEN
  179. ELSIF section.type = Sections.ConstSection THEN
  180. IF binarySection.os.alignment # 0 THEN
  181. INC(codeSize,(-codeSize) MOD binarySection.os.alignment);
  182. END;
  183. section.SetOffset(codeSize); INC(codeSize,binarySection.pc); (* global constants: in code *)
  184. Basic.Align(codeSize, 4); (* word alignment *)
  185. (*ReportSection(section)*)
  186. ELSIF (section.type = Sections.CodeSection) OR (section.type = Sections.BodyCodeSection) THEN
  187. (*IF section.symbol = module.module.moduleScope.bodyProcedure THEN
  188. bodyOffset := codeSize
  189. END;
  190. *)
  191. section.SetOffset(codeSize); INC(codeSize, binarySection.pc);
  192. Basic.Align(codeSize, 4); (* word alignment *)
  193. (*ReportSection(section)*)
  194. ELSIF section.type = Sections.VarSection THEN
  195. INC(varSize, binarySection.pc);
  196. IF binarySection.os.alignment # 0 THEN
  197. INC(varSize,(-varSize) MOD binarySection.os.alignment);
  198. END;
  199. section.SetOffset(-varSize); (* global variables: negative offset *)
  200. (*ReportSection(section)*)
  201. END
  202. END;
  203. END SetOffsets;
  204. (* note: if 'caseSections' is TRUE, only case table sections are processed, otherwise only regular sections (imported symbol/system call sections are never processed) *)
  205. PROCEDURE CopySections(sectionList: Sections.SectionList);
  206. VAR
  207. section: Sections.Section;
  208. i: LONGINT;
  209. BEGIN
  210. FOR i := 0 TO sectionList.Length() - 1 DO
  211. section := sectionList.GetSection(i);
  212. binarySection := section(IntermediateCode.Section).resolved;
  213. IF (section.type = Sections.CodeSection) OR (section.type = Sections.BodyCodeSection) OR (section.type = Sections.ConstSection) THEN
  214. Copy(binarySection,code,section.offset);
  215. END
  216. END;
  217. END CopySections;
  218. BEGIN
  219. FirstOffsets(module.allSections); (* regular sections *)
  220. SetOffsets(module.allSections); (* regular sections and case table sections -- a case table is a special case of a constant section *)
  221. NEW(code,codeSize );
  222. CopySections(module.allSections); (* regular sections *)
  223. END MakeSectionOffsets;
  224. PROCEDURE WriteObjectFile*(w:Streams.Writer; module: Sections.Module; symbolFile: Files.File; diagnostics: Diagnostics.Diagnostics): BOOLEAN;
  225. VAR codeSize, dataSize, bodyOffset: LONGINT;
  226. moduleScope: SyntaxTree.ModuleScope; fingerprinter: Fingerprinter.Fingerprinter;
  227. code: ByteArray;
  228. fp: SyntaxTree.Fingerprint;
  229. error : BOOLEAN;
  230. (** helper procedures *)
  231. PROCEDURE GetEntries(moduleScope: SyntaxTree.ModuleScope; VAR numberEntries: LONGINT; VAR entries: ARRAY 256 OF IntermediateCode.Section);
  232. VAR symbol: SyntaxTree.Symbol; p: Sections.Section;
  233. PROCEDURE ConstantNeedsSection(constant: SyntaxTree.Constant): BOOLEAN;
  234. BEGIN
  235. RETURN (constant.type.resolved IS SyntaxTree.StringType) OR (constant.type.resolved IS SyntaxTree.MathArrayType)
  236. END ConstantNeedsSection;
  237. PROCEDURE TypeNeedsSection(type: SyntaxTree.TypeDeclaration): BOOLEAN;
  238. BEGIN
  239. RETURN (type.declaredType.resolved IS SyntaxTree.RecordType)
  240. END TypeNeedsSection;
  241. BEGIN
  242. numberEntries := 0;
  243. symbol := moduleScope.firstSymbol;
  244. WHILE symbol # NIL DO
  245. IF (symbol.access * SyntaxTree.Public # {}) THEN
  246. IF (symbol IS SyntaxTree.Procedure) & ~(symbol(SyntaxTree.Procedure).isInline)
  247. OR (symbol IS SyntaxTree.Variable)
  248. OR (symbol IS SyntaxTree.TypeDeclaration) & TypeNeedsSection(symbol(SyntaxTree.TypeDeclaration))
  249. OR (symbol IS SyntaxTree.Constant) & (ConstantNeedsSection(symbol(SyntaxTree.Constant))) THEN
  250. INC(numberEntries); (* start at 1 !! *)
  251. p := module.allSections.FindBySymbol(symbol);
  252. IF p = NIL THEN
  253. p := module.importedSections.FindBySymbol(symbol);
  254. END;
  255. IF p # NIL THEN
  256. entries[numberEntries] := p(IntermediateCode.Section);
  257. IF Trace THEN
  258. IF moduleScope = module.module.moduleScope (* self *) THEN
  259. D.String("Entry "); D.Int(numberEntries,1); D.String(": "); D.Str0(symbol.name); D.String(" @"); D.Int(p.offset,1); D.Ln;
  260. END;
  261. END;
  262. ELSE
  263. IF Trace THEN
  264. IF moduleScope = module.module.moduleScope (* self *) THEN
  265. D.String("did not find entry for "); D.Str0(symbol.name); D.Ln;
  266. END
  267. END;
  268. entries[numberEntries] := NIL;
  269. END;
  270. END;
  271. END;
  272. symbol := symbol.nextSymbol;
  273. END;
  274. END GetEntries;
  275. PROCEDURE Put32(offset: LONGINT; number: LONGINT);
  276. BEGIN
  277. IF Trace THEN
  278. D.String("put32 at offset "); D.Int(offset,1);D.String(" : "); D.Hex(number,-8); D.Ln;
  279. END;
  280. code[offset] := CHR(number MOD 100H);
  281. INC(offset); number := number DIV 100H;
  282. code[offset] := CHR(number MOD 100H);
  283. INC(offset); number := number DIV 100H;
  284. code[offset] := CHR(number MOD 100H);
  285. INC(offset); number := number DIV 100H;
  286. code[offset] := CHR(number MOD 100H);
  287. END Put32;
  288. PROCEDURE Get32(offset: LONGINT): LONGINT;
  289. BEGIN
  290. RETURN ORD(code[offset]) + 100H*ORD(code[offset+1]) + 10000H * ORD(code[offset+2]) + 1000000H*ORD(code[offset+3]);
  291. END Get32;
  292. (* ObjectFile = name:String key:Int fixSelf:Int Imports Commands Entries Data Code *)
  293. PROCEDURE ObjectFile(bodyOffset: LONGINT);
  294. VAR moduleName: Name;
  295. PROCEDURE Resolve(fixup: BinaryCode.Fixup);
  296. BEGIN
  297. IF fixup.resolved = NIL THEN fixup.resolved := module.allSections.FindByName(fixup.symbol.name) END;
  298. IF fixup.resolved = NIL THEN fixup.resolved := module.importedSections.FindByName(fixup.symbol.name) END;
  299. END Resolve;
  300. PROCEDURE InModule(s: Basic.SegmentedName):BOOLEAN;
  301. VAR
  302. section: Sections.Section;
  303. i: LONGINT;
  304. BEGIN
  305. FOR i := 0 TO module.allSections.Length() - 1 DO
  306. section := module.allSections.GetSection(i);
  307. IF section.name = s THEN RETURN TRUE END
  308. END;
  309. RETURN FALSE
  310. END InModule;
  311. (* go through list of all sections and all fixups in sections and if it is a self fixup, chain it *)
  312. PROCEDURE FixSelf(): LONGINT;
  313. VAR prev,this,patch: LONGINT; section: Sections.Section;
  314. binarySection: BinaryCode.Section; fixup: BinaryCode.Fixup; i,patchOffset: LONGINT;
  315. msg, name: ARRAY 256 OF CHAR;
  316. BEGIN
  317. prev := 0;
  318. FOR i := 0 TO module.allSections.Length() - 1 DO
  319. section := module.allSections.GetSection(i);
  320. IF (section.type # Sections.InitCodeSection) THEN
  321. binarySection := section(IntermediateCode.Section).resolved;
  322. fixup := binarySection.fixupList.firstFixup;
  323. WHILE fixup # NIL DO
  324. IF (fixup.mode = BinaryCode.Relative) & InModule(fixup.symbol.name) THEN
  325. Basic.Error(diagnostics, module.moduleName, Basic.invalidPosition, "Relative self fixup not supported by Minos Object File.");
  326. ELSIF (fixup.mode = BinaryCode.Absolute) & InModule(fixup.symbol.name) THEN
  327. this := section.offset + fixup.offset; (* location of the fixup *)
  328. (*
  329. ASSERT(this < 8000H);
  330. ASSERT(this >= -8000H);
  331. *)
  332. Resolve(fixup);
  333. patchOffset := (fixup.resolved.offset + fixup.displacement);
  334. IF (patchOffset DIV 4 >= 8000H) OR (patchOffset DIV 4< -8000H)
  335. OR (patchOffset MOD 4 # 0)
  336. THEN
  337. msg := "fixup problem: ";
  338. Basic.SegmentedNameToString(fixup.symbol.name, name);
  339. Strings.Append(msg, name);
  340. Strings.Append(msg," : ");
  341. Strings.AppendInt(msg, patchOffset);
  342. Basic.Error(diagnostics, module.moduleName,Basic.invalidPosition, msg);
  343. error := TRUE
  344. END;
  345. patch := prev DIV 4 + 10000H * (patchOffset DIV 4);
  346. IF Trace THEN
  347. D.String("fix self "); Basic.WriteSegmentedName(D.Log, section.name); D.String("+"); D.Int(fixup.offset,1);
  348. D.String(" -> ");
  349. Basic.WriteSegmentedName(D.Log, fixup.symbol.name); D.String("+"); D.Int(fixup.displacement,1) ;
  350. D.Ln;
  351. END;
  352. Put32(this, patch);
  353. prev := this;
  354. ELSE (* external fixup, handled in imports *)
  355. END;
  356. fixup := fixup.nextFixup;
  357. END
  358. END
  359. END;
  360. RETURN prev DIV 4
  361. END FixSelf;
  362. BEGIN
  363. Global.ModuleFileName(module.module.name,module.module.context,moduleName);
  364. fp := fingerprinter.SymbolFP(module.module);
  365. w.RawString(moduleName); w.RawLInt(fp.public);
  366. w.RawLInt(FixSelf());
  367. Imports;
  368. Commands;
  369. Entries(bodyOffset);
  370. Data;
  371. Code;
  372. END ObjectFile;
  373. (* Imports = {name:String key:Int fix:Int} 0X:Char *)
  374. PROCEDURE Imports;
  375. VAR name: Name; import: SyntaxTree.Import; number: LONGINT; numberEntries: LONGINT; entries: ARRAY 256 OF IntermediateCode.Section;
  376. PROCEDURE IsFirstOccurence(import: SyntaxTree.Import): BOOLEAN; (*! inefficient *)
  377. VAR i: SyntaxTree.Import;
  378. BEGIN
  379. i := moduleScope.firstImport;
  380. WHILE (i # NIL) & (i.module # import.module) DO
  381. i := i.nextImport;
  382. END;
  383. RETURN i = import
  384. END IsFirstOccurence;
  385. PROCEDURE MakeFixups(): LONGINT;
  386. VAR prev,this,instr,i: LONGINT; section: Sections.Section; first: Fixup; numberFixups: LONGINT;
  387. BEGIN
  388. prev := 0;
  389. FOR i := 1 TO numberEntries DO
  390. section := entries[i];
  391. IF section # NIL THEN
  392. numberFixups := GetFixups(diagnostics, module, section, first);
  393. IF Trace THEN
  394. D.Int(numberFixups,1); D.String(" fixups "); Basic.WriteSegmentedName(D.Log, section.name); D.Ln;
  395. END;
  396. WHILE first # NIL DO
  397. this := first.fixupSection.offset + first.fixup.offset;
  398. instr := Get32(this);
  399. ASSERT(prev < 10000H); ASSERT(i < 100H);
  400. (*
  401. 31 ... 24 | 23 .. 16 | 16 .. 0
  402. opCode | pno | next
  403. *)
  404. instr := instr MOD 1000000H + i * 10000H + prev DIV 4;
  405. Put32(this, instr);
  406. prev := this;
  407. first := first.nextFixup;
  408. END;
  409. END;
  410. END;
  411. IF Trace THEN D.String(" fixup chain starting at "); D.Int(prev,1); D.Ln END;
  412. RETURN prev DIV 4
  413. END MakeFixups;
  414. BEGIN
  415. import := moduleScope.firstImport;
  416. WHILE(import # NIL) DO
  417. IF ~Global.IsSystemModule(import.module) & IsFirstOccurence(import) THEN
  418. Global.ModuleFileName(import.module.name,import.module.context,name);
  419. IF Trace THEN
  420. D.Str("Import module : "); D.Str(name); D.Ln;
  421. END;
  422. w.RawString(name);
  423. fp := fingerprinter.SymbolFP(import.module);
  424. w.RawLInt(fp.public);
  425. (* get all imported entries of imported module *)
  426. GetEntries(import.module.moduleScope, numberEntries, entries);
  427. (* generate fixups to all non-zero entries *)
  428. w.RawLInt(MakeFixups());
  429. END;
  430. import := import.nextImport;
  431. END;
  432. w.Char(0X);
  433. END Imports;
  434. (* Commands = {name:String offset:Int} 0X:Char *)
  435. PROCEDURE Commands;
  436. VAR
  437. procedure : SyntaxTree.Procedure; procedureType: SyntaxTree.ProcedureType;
  438. p: Sections.Section; name: Name; numberParameters, i: LONGINT;
  439. BEGIN
  440. FOR i := 0 TO module.allSections.Length() - 1 DO
  441. p := module.allSections.GetSection(i);
  442. IF (p.type # Sections.InitCodeSection) & (p.symbol # NIL) & (p.symbol IS SyntaxTree.Procedure) THEN
  443. procedure := p.symbol(SyntaxTree.Procedure);
  444. procedureType := procedure.type(SyntaxTree.ProcedureType);
  445. IF (SyntaxTree.PublicRead IN procedure.access) & ~(procedure.isInline) & ~(procedureType.isDelegate) & (procedureType.numberParameters = 0) THEN
  446. procedure.GetName(name);
  447. IF Trace THEN
  448. D.Str("Command : "); D.Str(name); D.Str(" @ "); D.Int(p.offset ,1);
  449. END;
  450. w.RawString(name);
  451. w.RawLInt(p.offset DIV 4);
  452. IF Trace THEN D.Ln END
  453. END
  454. END
  455. END;
  456. w.Char(0X);
  457. END Commands;
  458. (* noEntries:Int BodyEntry {entry:Int32}:noEntries *)
  459. PROCEDURE Entries(bodyOffset: LONGINT);
  460. VAR
  461. i,numberEntries: LONGINT; entry: ARRAY 256 OF IntermediateCode.Section; (* more is not allowed anyway in the runtime system *)
  462. BEGIN
  463. GetEntries(moduleScope, numberEntries, entry);
  464. w.RawLInt(numberEntries);
  465. w.RawLInt(0); (* body entry: body is fixed at position 0, cf. MakeSectionOffsets *)
  466. FOR i := 1 TO numberEntries DO
  467. ASSERT(entry[i].offset MOD 4 = 0);
  468. w.RawLInt(entry[i].offset DIV 4); (* entries here must be byte wise because jumps take place with absolute fixup - I cannot distinguish here *)
  469. END;
  470. END Entries;
  471. (* dataSize:Int32 *)
  472. PROCEDURE Data;
  473. BEGIN
  474. w.RawLInt(dataSize);
  475. END Data;
  476. (* codeLen:Int32 {code:Int32}:codeLen *)
  477. PROCEDURE Code;
  478. VAR i: LONGINT;
  479. BEGIN
  480. ASSERT(codeSize MOD 4 = 0);
  481. w.RawLInt(codeSize DIV 4);
  482. FOR i := 0 TO codeSize-1 DO
  483. w.Char(code[i]);
  484. END;
  485. END Code;
  486. BEGIN
  487. error := FALSE;
  488. moduleScope := module.module.moduleScope;
  489. NEW(fingerprinter);
  490. MakeSectionOffsets(module,dataSize,codeSize,bodyOffset,code); (* --> all sections are now assembled as one piece in code *)
  491. ObjectFile(bodyOffset);
  492. w.Update;
  493. RETURN ~error
  494. END WriteObjectFile;
  495. PROCEDURE Get*(): Formats.ObjectFileFormat;
  496. VAR objectFileFormat: ObjectFileFormat;
  497. BEGIN NEW(objectFileFormat); RETURN objectFileFormat
  498. END Get;
  499. END FoxMinosObjectFile.
  500. System.Free FoxMinosObjectFile ~