FoxMinosObjectFile.Mod 20 KB

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