FoxMinosObjectFile.Mod 19 KB

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