Info.Mod 28 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890
  1. (* Aos, Copyright 2001, Pieter Muller, ETH Zurich *)
  2. MODULE Info; (** AUTHOR "pjm/staubesv"; PURPOSE "System information"; *)
  3. IMPORT
  4. SYSTEM, Machine, Heaps, Objects, Streams, Reflection, Modules, Commands, Options, Strings, D := Debugging, Kernel;
  5. CONST
  6. AddressSize = SIZEOF(ADDRESS);
  7. RecordBlock = 1;
  8. ProtRecBlock = 2;
  9. ArrayBlock = 3;
  10. SystemBlock = 4;
  11. MaxNofTypes = 2048;
  12. (* Analyzer.Sort *)
  13. SortNone = 0;
  14. SortByCount = 1;
  15. SortBySize = 2;
  16. SortByTotalSize = 3; (* whereas TotalSize = Count * Size *)
  17. SortByName = 4;
  18. AllocatorHistorySize = 4096; (* recent history of allocators to be able to trace memory wasting sources *)
  19. TYPE
  20. Type = RECORD
  21. ptag : ADDRESS;
  22. count : LONGINT;
  23. size : SIZE;
  24. type : SHORTINT;
  25. pc: ADDRESS;
  26. END;
  27. Analyzer = OBJECT
  28. VAR
  29. types : POINTER TO ARRAY OF Type;
  30. nofElements : LONGINT;
  31. (* global statistics *)
  32. nofHeapBlocks, nofFreeBlocks, nofSystemBlocks, nofRecordBlocks, nofProtRecBlocks, nofArrayBlocks: LONGINT;
  33. sizeHeapBlocks, sizeFreeBlocks, sizeSystemBlocks, sizeRecordBlocks, sizeProtRecBlocks, sizeArrayBlocks: SIZE;
  34. PROCEDURE &Init(size : LONGINT);
  35. BEGIN
  36. ASSERT(size > 0);
  37. NEW(types, size);
  38. Reset;
  39. END Init;
  40. PROCEDURE Reset;
  41. VAR i : LONGINT;
  42. BEGIN
  43. nofElements := 0;
  44. IF (types # NIL) THEN
  45. FOR i := 0 TO LEN(types)-1 DO
  46. types[i].ptag := Heaps.NilVal;
  47. types[i].count := 0;
  48. types[i].size := 0;
  49. END;
  50. END;
  51. nofHeapBlocks := 0; sizeHeapBlocks := 0;
  52. nofFreeBlocks := 0; sizeFreeBlocks := 0;
  53. nofSystemBlocks := 0; sizeSystemBlocks := 0;
  54. nofRecordBlocks := 0; sizeRecordBlocks := 0;
  55. nofProtRecBlocks := 0; sizeProtRecBlocks := 0;
  56. nofArrayBlocks := 0; sizeArrayBlocks := 0;
  57. END Reset;
  58. PROCEDURE SortBy(mode : LONGINT);
  59. VAR i, j : LONGINT; temp : Type;
  60. PROCEDURE IsGreaterThan(CONST entry1, entry2 : Type; mode : LONGINT) : BOOLEAN;
  61. VAR name1, name2: ARRAY 256 OF CHAR; count1,count2, size1, size2: SIZE;
  62. BEGIN
  63. IF mode = SortByName THEN
  64. GetName(entry1.ptag,name1);
  65. GetName(entry2.ptag,name2);
  66. RETURN name1 > name2;
  67. ELSE
  68. count1 := entry1.count;
  69. size1 := entry1.size DIV count1;
  70. count2 := entry2.count;
  71. size2 := entry2.size DIV count2;
  72. RETURN
  73. ((mode = SortByCount) & (count1 > count2)) OR
  74. ((mode = SortBySize) & (size1 > size2)) OR
  75. ((mode = SortByTotalSize) & (size1*count1 > size2 * count2))
  76. ;
  77. END;
  78. END IsGreaterThan;
  79. BEGIN
  80. ASSERT((mode = SortByCount) OR (mode = SortBySize) OR (mode = SortByTotalSize) OR (mode=SortByName));
  81. (* sort descending... *)
  82. FOR i := 0 TO nofElements-1 DO
  83. FOR j := 1 TO nofElements-1 DO
  84. IF IsGreaterThan(types[j], types[j-1], mode) THEN
  85. temp := types[j-1];
  86. types[j-1] := types[j];
  87. types[j] := temp;
  88. END;
  89. END;
  90. END;
  91. END SortBy;
  92. PROCEDURE Add(CONST block : Heaps.HeapBlock; byPC: BOOLEAN);
  93. VAR type: SHORTINT;
  94. PROCEDURE AddByType(type: SHORTINT);
  95. VAR tag: ADDRESS; i: LONGINT;
  96. BEGIN
  97. SYSTEM.GET(block.dataAdr + Heaps.TypeDescOffset, tag);
  98. i := 0; WHILE (i < LEN(types)) & (i < nofElements) & (types[i].ptag # tag) DO INC(i) END;
  99. IF (i < nofElements) THEN
  100. INC(types[i].count);
  101. INC(types[i].size, block.size);
  102. ELSIF (i = nofElements) & (i < LEN(types)) THEN
  103. types[i].ptag := tag;
  104. types[i].count := 1;
  105. types[i].size := block.size;
  106. types[i].type := type;
  107. types[i].pc := 0;
  108. INC(nofElements)
  109. END;
  110. END AddByType;
  111. PROCEDURE AddByPC(type: SHORTINT);
  112. VAR pc: ADDRESS; i: LONGINT;
  113. BEGIN
  114. SYSTEM.GET(block.dataAdr + Heaps.HeapBlockOffset, pc);
  115. SYSTEM.GET(pc + Heaps.HeapBlockOffset, pc);
  116. IF pc # 0 THEN
  117. i := 0; WHILE (i < LEN(types)) & (i < nofElements) & (types[i].pc # pc) DO INC(i) END;
  118. IF (i < nofElements) THEN
  119. INC(types[i].count);
  120. INC(types[i].size, block.size);
  121. ELSIF (i = nofElements) & (i < LEN(types)) THEN
  122. types[i].ptag := 0;
  123. types[i].count := 1;
  124. types[i].size := block.size;
  125. types[i].type := type;
  126. types[i].pc := pc;
  127. INC(nofElements)
  128. END;
  129. END;
  130. END AddByPC;
  131. BEGIN
  132. INC(nofHeapBlocks); INC(sizeHeapBlocks, block.size);
  133. IF (block IS Heaps.RecordBlock) OR (block IS Heaps.ProtRecBlock) OR (block IS Heaps.ArrayBlock) THEN
  134. IF (block IS Heaps.ProtRecBlock) THEN
  135. type := ProtRecBlock;
  136. INC(nofProtRecBlocks); INC(sizeProtRecBlocks, block.size);
  137. ELSIF (block IS Heaps.RecordBlock) THEN
  138. type := RecordBlock;
  139. INC(nofRecordBlocks); INC(sizeRecordBlocks, block.size);
  140. ELSIF (block IS Heaps.ArrayBlock) THEN
  141. type := ArrayBlock;
  142. INC(nofArrayBlocks); INC(sizeArrayBlocks, block.size);
  143. ELSE
  144. HALT(99);
  145. END;
  146. IF byPC THEN
  147. AddByPC(type)
  148. ELSE
  149. (* all these heap blocks have a type tag *)
  150. AddByType(type)
  151. END;
  152. ELSIF (block IS Heaps.SystemBlock) THEN
  153. INC(nofSystemBlocks); INC(sizeSystemBlocks, block.size);
  154. (* system blocks do not have a type tag *)
  155. AddByPC(SystemBlock);
  156. ELSIF (block IS Heaps.FreeBlock) THEN
  157. INC(nofFreeBlocks); INC(sizeFreeBlocks, block.size);
  158. END;
  159. END Add;
  160. PROCEDURE ShowBlocks(CONST mask : ARRAY OF CHAR; out : Streams.Writer);
  161. VAR
  162. module : Modules.Module; typedesc : Modules.TypeDesc;
  163. size, totalSize: SIZE;
  164. startpc: ADDRESS;
  165. i, selected, total : LONGINT;
  166. string : ARRAY 256 OF CHAR; copy: ARRAY 256 OF CHAR;
  167. BEGIN
  168. ASSERT(out # NIL);
  169. size := 0; totalSize := 0;
  170. selected := 0; total := 0;
  171. FOR i := 0 TO nofElements-1 DO
  172. INC(total, types[i].count);
  173. module := NIL;
  174. IF (types[i].pc # 0) THEN
  175. module := Modules.ThisModuleByAdr(types[i].pc);
  176. ELSIF (types[i].ptag # 0) THEN
  177. Modules.ThisTypeByAdr(types[i].ptag, module, typedesc);
  178. END;
  179. IF (module # NIL) THEN
  180. IF (types[i].ptag # 0) THEN
  181. string := "";
  182. COPY(module.name,copy);
  183. Strings.AppendX(string, copy);
  184. Strings.AppendX(string, ".");
  185. COPY(typedesc.name,copy);
  186. Strings.AppendX(string, copy);
  187. ELSE
  188. string := "";
  189. COPY(module.name,copy);
  190. Strings.AppendX(string, copy);
  191. Strings.AppendX(string, ".");
  192. Reflection.GetProcedureName(types[i].pc, copy,startpc);
  193. Strings.AppendX(string, copy);
  194. Strings.Append(string,":");
  195. Strings.IntToStr(LONGINT(types[i].pc - startpc), copy);
  196. Strings.Append(string,copy);
  197. END;
  198. IF Strings.Match(mask, string) THEN
  199. CASE types[i].type OF
  200. |RecordBlock: out.String("R ");
  201. |ProtRecBlock: out.String("P ");
  202. |ArrayBlock: out.String("A ");
  203. |SystemBlock: out.String("S ");
  204. ELSE
  205. out.String("U ");
  206. END;
  207. INC(selected, types[i].count);
  208. out.Int(types[i].count, 8); out.Char(" ");
  209. INC(size, types[i].size);
  210. out.Int(types[i].size DIV types[i].count, 6); out.String("B ");
  211. out.Int(types[i].size, 10); out.String("B ");
  212. out.String(string);
  213. out.String(" (total ");
  214. WriteB(types[i].size, out); out.String(")"); out.Ln
  215. END;
  216. END;
  217. END;
  218. out.Ln;
  219. IF (selected # total) THEN
  220. out.String("Selected "); out.Int(selected, 1); out.String(" of ");
  221. out.Int(total, 1); out.String(" dynamic records of ");
  222. out.Int(nofElements, 1); out.String(" unique types (total size : ");
  223. WriteB(size, out); out.String(" of "); WriteB(totalSize, out); out.String(")");
  224. out.Ln;
  225. ELSE
  226. out.Int(total, 1); out.String(" dynamic records of ");
  227. out.Int(nofElements, 1); out.String(" unique types found");
  228. out.String(" (total size : "); WriteB(sizeHeapBlocks, out); out.String(")");
  229. out.Ln;
  230. END;
  231. END ShowBlocks;
  232. PROCEDURE Show(out : Streams.Writer; CONST mask : ARRAY OF CHAR; sortMode : LONGINT; byPC: BOOLEAN);
  233. VAR nofUsedBlocks, sizeUsedBlocks :SIZE;
  234. PROCEDURE ShowBlock(CONST name : ARRAY OF CHAR; nofBlocks: SIZE; size: SIZE; totalNofBlocks: SIZE; totalSize : SIZE; out : Streams.Writer);
  235. BEGIN
  236. out.Int(nofBlocks, 8); out.Char(" "); ShowPercent(nofBlocks, totalNofBlocks, out); out.Char(" ");
  237. out.String(name);
  238. out.String(" ("); WriteB(size, out); out.String(", "); ShowPercent(size, totalSize, out); out.String(")");
  239. out.Ln;
  240. END ShowBlock;
  241. PROCEDURE ShowPercent(cur, max : SIZE; out : Streams.Writer);
  242. VAR percent : LONGINT;
  243. BEGIN
  244. IF (max > 0) THEN
  245. percent := ENTIER(100 * (cur / max) + 0.5);
  246. ELSE
  247. percent := 0;
  248. END;
  249. IF (percent < 10) THEN out.String(" ");
  250. ELSIF (percent < 100) THEN out.Char(" ");
  251. END;
  252. out.Int(percent, 0); out.Char("%");
  253. END ShowPercent;
  254. BEGIN
  255. ASSERT(out # NIL);
  256. nofUsedBlocks := nofHeapBlocks - nofFreeBlocks;
  257. sizeUsedBlocks := sizeHeapBlocks - sizeFreeBlocks;
  258. out.Char(0EX); (* non-proportional font *)
  259. ShowBlock("HeapBlocks", nofHeapBlocks, sizeHeapBlocks, nofHeapBlocks, sizeHeapBlocks, out);
  260. ShowBlock("UsedBlocks", nofUsedBlocks, sizeUsedBlocks, nofHeapBlocks, sizeHeapBlocks, out);
  261. ShowBlock("FreeBlocks", nofFreeBlocks, sizeFreeBlocks, nofHeapBlocks, sizeHeapBlocks, out);
  262. out.Ln;
  263. ShowBlock("UsedBlocks", nofUsedBlocks, sizeUsedBlocks, nofUsedBlocks, sizeUsedBlocks, out);
  264. ShowBlock("SystemBlocks", nofSystemBlocks, sizeSystemBlocks, nofUsedBlocks, sizeUsedBlocks, out);
  265. ShowBlock("RecordBlocks", nofRecordBlocks, sizeRecordBlocks, nofUsedBlocks, sizeUsedBlocks, out);
  266. ShowBlock("ProtRectBlocks", nofProtRecBlocks, sizeProtRecBlocks, nofUsedBlocks, sizeUsedBlocks, out);
  267. ShowBlock("ArrayBlocks", nofArrayBlocks, sizeArrayBlocks, nofUsedBlocks, sizeUsedBlocks, out);
  268. IF (mask # "") THEN
  269. out.Ln;
  270. IF (sortMode = SortByCount) OR (sortMode = SortBySize) OR (sortMode = SortByTotalSize) OR (sortMode = SortByName) THEN
  271. SortBy(sortMode);
  272. END;
  273. ShowBlocks(mask, out);
  274. END;
  275. out.Char(0FX); (* proportional font *)
  276. END Show;
  277. END Analyzer;
  278. VAR
  279. currentMarkValueAddress : ADDRESS;
  280. recentAllocators*: ARRAY AllocatorHistorySize OF RECORD pc*: ARRAY 3 OF ADDRESS; time*: HUGEINT END;
  281. numRecentAllocators*: LONGINT;
  282. PROCEDURE LogAlloc(p: ANY);
  283. VAR time: HUGEINT; bp: ADDRESS; i: LONGINT;pc: ADDRESS;
  284. BEGIN
  285. time := Machine.GetTimer();
  286. bp := SYSTEM.GetFramePointer();
  287. SYSTEM.GET(bp+SIZEOF(ADDRESS),pc);
  288. FOR i := 0 TO LEN(recentAllocators[numRecentAllocators].pc)-1 DO
  289. recentAllocators[numRecentAllocators].pc[i] := pc;
  290. IF bp # 0 THEN
  291. SYSTEM.GET(bp, bp);
  292. SYSTEM.GET(bp+SIZEOF(ADDRESS),pc);
  293. END;
  294. END;
  295. recentAllocators[numRecentAllocators].time := time;
  296. INC(numRecentAllocators); numRecentAllocators := numRecentAllocators MOD LEN(recentAllocators);
  297. END LogAlloc;
  298. PROCEDURE WriteB(b : SIZE; out : Streams.Writer);
  299. VAR shift : LONGINT; suffix : ARRAY 2 OF CHAR;
  300. BEGIN
  301. IF b < 100*1024 THEN suffix := ""; shift := 0
  302. ELSIF b < 100*1024*1024 THEN suffix := "K"; shift := -10
  303. ELSE suffix := "M"; shift := -20
  304. END;
  305. IF b # ASH(ASH(b, shift), -shift) THEN out.Char("~") END;
  306. out.Int(ASH(b, shift), 1);
  307. IF TRUE THEN
  308. out.String(suffix); out.Char("B")
  309. ELSE
  310. out.Char(" ");
  311. out.String(suffix); out.String("byte");
  312. IF b # 1 THEN out.Char("s") END
  313. END
  314. END WriteB;
  315. (** Show the details of the specified module. *)
  316. PROCEDURE ModuleDetails*(context : Commands.Context); (** [Options] module ~ *)
  317. VAR
  318. m : Modules.Module; i, j, k: LONGINT;
  319. p, procAdr: ADDRESS;
  320. adr : ADDRESS;
  321. modn : ARRAY 33 OF CHAR;
  322. options : Options.Options;
  323. BEGIN
  324. NEW(options);
  325. options.Add("d", "details", Options.Flag);
  326. IF options.Parse(context.arg, context.error) THEN
  327. context.arg.SkipWhitespace; context.arg.String(modn);
  328. m := Modules.root;
  329. WHILE (m # NIL) & (m.name # modn) DO m := m.next END;
  330. IF m # NIL THEN
  331. context.out.String(m.name);
  332. context.out.String(" refcnt = "); context.out.Int(m.refcnt, 1);
  333. context.out.String(" sb ="); context.out.Hex(m.sb, 9);
  334. context.out.String(" dataSize = "); context.out.Int(LEN(m.data), 1);
  335. context.out.String(" staticTdSize = "); context.out.Int(LEN(m.staticTypeDescs), 1);
  336. context.out.String(" codeSize = "); context.out.Int(LEN(m.code), 1);
  337. context.out.String(" refSize = "); context.out.Int(LEN(m.refs), 1);
  338. context.out.String(" entries = "); context.out.Int(LEN(m.entry), 1);
  339. context.out.String(" commands = "); context.out.Int(LEN(m.command), 1);
  340. context.out.String(" modules = "); context.out.Int(LEN(m.module), 1);
  341. context.out.String(" types = "); context.out.Int(LEN(m.typeInfo), 1);
  342. context.out.String(" pointers = "); context.out.Int(LEN(m.ptrAdr), 1);
  343. context.out.Ln; context.out.String(" ptrAdr:");
  344. FOR i := 0 TO LEN(m.ptrAdr)-1 DO
  345. context.out.Char(" "); context.out.Int(m.ptrAdr[i]-m.sb, 1)
  346. END;
  347. context.out.Ln;
  348. IF options.GetFlag("details") THEN
  349. context.out.String("Pointer Details: ");
  350. IF (m.ptrAdr # NIL) THEN
  351. context.out.Ln;
  352. FOR i := 0 TO LEN(m.ptrAdr) - 1 DO
  353. context.out.Int(i, 0); context.out.String(": ");
  354. context.out.Address(m.ptrAdr[i]); context.out.String(" -> ");
  355. SYSTEM.GET(m.ptrAdr[i], adr);
  356. context.out.Address(adr);
  357. context.out.Ln;
  358. END;
  359. ELSE
  360. context.out.String("none"); context.out.Ln;
  361. END;
  362. END;
  363. FOR i := 0 TO LEN(m.typeInfo) - 1 DO
  364. context.out.Ln; context.out.String(" type:");
  365. context.out.Hex(m.typeInfo[i].tag, 9);
  366. context.out.Char(" "); context.out.String(m.typeInfo[i].name);
  367. context.out.Hex(SYSTEM.VAL(LONGINT, m.typeInfo[i].flags), 9);
  368. (* type descriptor info *)
  369. context.out.Ln; context.out.String(" typedesc1:");
  370. p := m.typeInfo[i].tag; (* address of static type descriptor *)
  371. REPEAT
  372. SYSTEM.GET(p, k);
  373. IF ABS(k) <= 4096 THEN context.out.Char(" "); context.out.Int(k, 1)
  374. ELSE context.out.Hex(k, 9)
  375. END;
  376. INC(p, AddressSize)
  377. UNTIL k < -40000000H;
  378. (* methods *)
  379. context.out.Ln; context.out.String(" typedescmths:");
  380. p := SYSTEM.VAL(ADDRESS, m.typeInfo[i].tag) + Modules.Mth0Ofs;
  381. j := 0;
  382. SYSTEM.GET(p, procAdr);
  383. WHILE procAdr # Heaps.MethodEndMarker DO
  384. context.out.Ln; context.out.Int(j, 3); context.out.Char(" ");
  385. Reflection.WriteProc(context.out, procAdr);
  386. DEC(p, AddressSize);
  387. SYSTEM.GET(p, procAdr);
  388. INC(j)
  389. END
  390. END;
  391. context.out.Ln
  392. END;
  393. END;
  394. END ModuleDetails;
  395. (** Find a procedure, given the absolute PC address. *)
  396. PROCEDURE ModulePC*(context : Commands.Context); (** pc *)
  397. VAR pc : LONGINT;
  398. BEGIN
  399. context.arg.SkipWhitespace; context.arg.Int(pc, FALSE);
  400. IF Modules.ThisModuleByAdr(pc) # NIL THEN
  401. Reflection.WriteProc(context.out, pc);
  402. ELSE
  403. context.out.Hex(pc, 8); context.out.String(" not found")
  404. END;
  405. context.out.Ln;
  406. END ModulePC;
  407. PROCEDURE AllObjects*(context : Commands.Context); (** [Options] mask ~ *)
  408. VAR
  409. options : Options.Options; sortMode : LONGINT;
  410. analyzer : Analyzer;
  411. memBlock {UNTRACED}: Machine.MemoryBlock;
  412. heapBlock : Heaps.HeapBlock;
  413. p : ADDRESS;
  414. mask : ARRAY 128 OF CHAR;
  415. BEGIN
  416. NEW(options);
  417. options.Add("s", "sort", Options.Integer);
  418. options.Add(0X, "pc", Options.Flag);
  419. options.Add(0X, "gc", Options.Flag);
  420. IF options.Parse(context.arg, context.error) THEN
  421. IF ~options.GetInteger("sort", sortMode) THEN sortMode := SortNone; END;
  422. context.arg.SkipWhitespace; context.arg.String(mask);
  423. NEW(analyzer, MaxNofTypes);
  424. IF options.GetFlag("gc") THEN Heaps.LazySweepGC END; (* slight inaccuracy here: other processes can kick in now *)
  425. Machine.Acquire(Machine.Heaps);
  426. Heaps.FullSweep(); (* the heap might contain wrong pointers in the freed part *)
  427. memBlock := Machine.memBlockHead;
  428. WHILE memBlock # NIL DO
  429. p := memBlock.beginBlockAdr;
  430. WHILE p # memBlock.endBlockAdr DO
  431. heapBlock := SYSTEM.VAL(Heaps.HeapBlock, p + Heaps.BlockHeaderSize); (* get heap block *)
  432. analyzer.Add(heapBlock, options.GetFlag("pc"));
  433. p := p + heapBlock.size
  434. END;
  435. memBlock := memBlock.next
  436. END;
  437. Machine.Release(Machine.Heaps);
  438. analyzer.Show(context.out, mask, sortMode, options.GetFlag("pc"));
  439. END;
  440. END AllObjects;
  441. PROCEDURE ShowRecentAllocators*(out: Streams.Writer; scale: HUGEINT);
  442. VAR
  443. i,from,to,num, pcs: LONGINT;
  444. pc,startpc: ADDRESS;
  445. module: Modules.Module; name: ARRAY 256 OF CHAR;
  446. time: HUGEINT;
  447. timer: Kernel.MilliTimer;
  448. BEGIN
  449. time := Machine.GetTimer();
  450. IF scale <= 0 THEN
  451. Kernel.SetTimer( timer, 100 ); scale := Machine.GetTimer();
  452. WHILE ~Kernel.Expired( timer ) DO END;
  453. scale := (Machine.GetTimer() - scale) DIV 100; (* 1 ms resolution *)
  454. END;
  455. out.String("----------- recent allocators, t = ");
  456. out.Hex(recentAllocators[i].time, -16);
  457. out.String(" ---------------"); out.Ln;
  458. Machine.Acquire(Machine.Heaps);
  459. i := numRecentAllocators;
  460. DEC(i); i := i MOD LEN(recentAllocators);
  461. from := i;
  462. pc := recentAllocators[i].pc[0];
  463. WHILE (i # numRecentAllocators) & (pc # 0) DO
  464. DEC(i); i := i MOD LEN(recentAllocators);
  465. pc := recentAllocators[i].pc[0];
  466. END;
  467. to := i;
  468. Machine.Release(Machine.Heaps);
  469. i := from; num := 0;
  470. WHILE i # to DO
  471. out.Int(num,1); out.String(": ");
  472. out.Hex(recentAllocators[i].time, -16);
  473. out.String("(");
  474. out.Int( SHORT((recentAllocators[i].time-time) DIV scale), 1);
  475. out.String(")");
  476. out.String(": ");
  477. FOR pcs := 0 TO LEN(recentAllocators[i].pc)-1 DO
  478. pc := recentAllocators[i].pc[pcs];
  479. module := Modules.ThisModuleByAdr(pc);
  480. out.String(module.name);
  481. out.String(".");
  482. Reflection.GetProcedureName(pc, name,startpc);
  483. out.String(name);
  484. out.String(":");
  485. out.Int(pc-startpc,1);
  486. out.String(" ");
  487. END;
  488. out.Ln;
  489. DEC(i); i := i MOD LEN(recentAllocators);
  490. INC(num);
  491. END;
  492. END ShowRecentAllocators;
  493. PROCEDURE ClearRecentAllocators*;
  494. VAR i: LONGINT;
  495. BEGIN
  496. Machine.Acquire(Machine.Heaps);
  497. i := (numRecentAllocators - 1) MOD LEN(recentAllocators);
  498. recentAllocators[i].pc[0] := 0;
  499. Machine.Release(Machine.Heaps);
  500. END ClearRecentAllocators;
  501. PROCEDURE AddAllocatorLogger*;
  502. BEGIN
  503. Heaps.SetAllocationLogger(LogAlloc);
  504. END AddAllocatorLogger;
  505. PROCEDURE RecentAllocators*(context : Commands.Context); (** [Options] mask ~ *)
  506. VAR
  507. options : Options.Options;
  508. scale: HUGEINT;
  509. num: LONGINT;
  510. BEGIN
  511. NEW(options);
  512. options.Add("c", "clear", Options.Flag);
  513. options.Add("s", "scale", Options.Integer);
  514. IF options.Parse(context.arg, context.error) THEN
  515. IF options.GetInteger("scale", num) & (num > 0 ) THEN
  516. scale := num
  517. ELSE (* autoscale to ms *)
  518. scale := 0;
  519. END;
  520. ShowRecentAllocators(context.out, scale);
  521. IF options.GetFlag("clear") THEN ClearRecentAllocators END;
  522. END;
  523. END RecentAllocators;
  524. PROCEDURE TraceModule*(context : Commands.Context); (** moduleName mask ~ *)
  525. VAR
  526. options : Options.Options; sortMode : LONGINT;
  527. analyzer : Analyzer;
  528. mask : ARRAY 128 OF CHAR;
  529. moduleName : Modules.Name; module : Modules.Module;
  530. BEGIN
  531. NEW(options);
  532. options.Add("s", "sort", Options.Integer);
  533. IF options.Parse(context.arg, context.error) THEN
  534. IF ~options.GetInteger("sort", sortMode) THEN sortMode := SortNone; END;
  535. context.arg.SkipWhitespace; context.arg.String(moduleName);
  536. context.arg.SkipWhitespace; context.arg.String(mask);
  537. module := Modules.ModuleByName(moduleName);
  538. IF (module # NIL) THEN
  539. NEW(analyzer, MaxNofTypes);
  540. Machine.Acquire(Machine.Heaps);
  541. IncrementCurrentMarkValue;
  542. module.FindRoots;
  543. AnalyzeMarkedBlocks(analyzer);
  544. Machine.Release(Machine.Heaps);
  545. context.out.String("Heap block referenced by module "); context.out.String(moduleName); context.out.Char(":");
  546. context.out.Ln;
  547. analyzer.Show(context.out, mask, sortMode, FALSE);
  548. ELSE
  549. context.error.String("Module "); context.error.String(moduleName); context.error.String(" is not loaded."); context.error.Ln;
  550. END;
  551. END;
  552. END TraceModule;
  553. PROCEDURE TraceReference*(context : Commands.Context); (** ModuleName.VariableName mask ~ *)
  554. VAR
  555. options : Options.Options; sortMode : LONGINT;
  556. analyzer : Analyzer; address : ADDRESS;
  557. module : Modules.Module; variable : Reflection.Variable;
  558. mask, modVar : ARRAY 256 OF CHAR; array : Strings.StringArray;
  559. varName : ARRAY 64 OF CHAR;
  560. BEGIN
  561. NEW(options);
  562. options.Add("s", "sort", Options.Integer);
  563. IF options.Parse(context.arg, context.error) THEN
  564. IF ~options.GetInteger("sort", sortMode) THEN sortMode := SortNone; END;
  565. context.arg.SkipWhitespace; context.arg.String(modVar);
  566. context.arg.SkipWhitespace; context.arg.String(mask);
  567. array := Strings.Split(modVar, ".");
  568. IF (LEN(array) = 2) THEN
  569. module := Modules.ModuleByName(array[0]^);
  570. IF (module # NIL) THEN
  571. COPY(array[1]^, varName);
  572. IF Reflection.FindVar(module, varName, variable) THEN
  573. IF (variable.type = 13) OR (variable.type = 29) THEN
  574. NEW(analyzer, MaxNofTypes);
  575. context.out.String("Heap blocks reference by variable "); context.out.String(modVar);
  576. context.out.Char(":"); context.out.Ln;
  577. IF (variable.adr # 0) THEN
  578. SYSTEM.GET(variable.adr, address);
  579. MarkReference(analyzer, SYSTEM.VAL(ANY, address));
  580. analyzer.Show(context.out, mask, sortMode, FALSE);
  581. END;
  582. ELSE
  583. context.error.String("Variable is not a pointer"); context.error.Ln;
  584. END;
  585. ELSE
  586. context.error.String("Variable "); context.error.String(array[1]^); context.error.String(" not found");
  587. context.error.Ln;
  588. END;
  589. ELSE
  590. context.error.String("Module "); context.error.String(array[0]^); context.error.String(" not found");
  591. context.error.Ln;
  592. END;
  593. ELSE
  594. context.error.String("Expected ModuleName.VariableName parameter"); context.error.Ln;
  595. END;
  596. END;
  597. END TraceReference;
  598. PROCEDURE MarkReference(analyzer : Analyzer; ref : ANY);
  599. BEGIN
  600. ASSERT(analyzer # NIL);
  601. Machine.Acquire(Machine.Heaps);
  602. IncrementCurrentMarkValue;
  603. Heaps.Mark(ref);
  604. AnalyzeMarkedBlocks(analyzer);
  605. Machine.Release(Machine.Heaps);
  606. END MarkReference;
  607. PROCEDURE TraceProcessID*(context : Commands.Context); (** ProcessID mask ~ *)
  608. VAR
  609. options : Options.Options; sortMode : LONGINT;
  610. analyzer : Analyzer;
  611. process : Objects.Process;
  612. processID : LONGINT; mask : ARRAY 256 OF CHAR;
  613. BEGIN
  614. NEW(options);
  615. options.Add("s", "sort", Options.Integer);
  616. IF options.Parse(context.arg, context.error) THEN
  617. IF ~options.GetInteger("sort", sortMode) THEN sortMode := SortNone; END;
  618. IF context.arg.GetInteger(processID, FALSE) THEN
  619. context.arg.SkipWhitespace; context.arg.String(mask);
  620. process := FindProcessByID(processID);
  621. IF (process # NIL) THEN
  622. NEW(analyzer, MaxNofTypes);
  623. Machine.Acquire(Machine.Heaps);
  624. IncrementCurrentMarkValue;
  625. process.FindRoots;
  626. Heaps.CheckCandidates;
  627. AnalyzeMarkedBlocks(analyzer);
  628. Machine.Release(Machine.Heaps);
  629. context.out.String("Heap blocks referenced by process ID = "); context.out.Int(processID, 0); context.out.Char(":");
  630. context.out.Ln;
  631. analyzer.Show(context.out, mask, sortMode, FALSE);
  632. ELSE
  633. context.error.String("Process ID = "); context.error.Int(processID, 0); context.error.String(" not found");
  634. context.error.Ln;
  635. END;
  636. ELSE
  637. context.error.String("Expected ProcessID parameter"); context.error.Ln;
  638. END;
  639. END;
  640. END TraceProcessID;
  641. PROCEDURE FindProcessByID(id : LONGINT) : Objects.Process;
  642. VAR
  643. memBlock {UNTRACED}: Machine.MemoryBlock;
  644. heapBlock {UNTRACED}: Heaps.HeapBlock;
  645. blockAdr, tag : ADDRESS;
  646. process : Objects.Process;
  647. i : LONGINT;
  648. BEGIN
  649. i := 0;
  650. Machine.Acquire(Machine.Heaps);
  651. process := NIL;
  652. memBlock := Machine.memBlockHead;
  653. WHILE (memBlock # NIL) & (process = NIL) DO
  654. blockAdr := memBlock.beginBlockAdr;
  655. WHILE (blockAdr # memBlock.endBlockAdr) & (process = NIL) DO
  656. heapBlock := SYSTEM.VAL(Heaps.HeapBlock, blockAdr + Heaps.BlockHeaderSize);
  657. IF (heapBlock IS Heaps.RecordBlock) THEN
  658. SYSTEM.GET(heapBlock.dataAdr + Heaps.TypeDescOffset, tag);
  659. IF (tag = SYSTEM.TYPECODE(Objects.Process)) THEN
  660. process := SYSTEM.VAL(Objects.Process, heapBlock.dataAdr);
  661. IF (process.id # id) THEN process := NIL; END;
  662. END;
  663. END;
  664. blockAdr := blockAdr + heapBlock.size
  665. END;
  666. memBlock := memBlock.next
  667. END;
  668. Machine.Release(Machine.Heaps);
  669. RETURN process;
  670. END FindProcessByID;
  671. (* Caller MUST hold Machine.Heaps lock!! *)
  672. PROCEDURE AnalyzeMarkedBlocks(analyzer : Analyzer);
  673. VAR
  674. memBlock {UNTRACED}: Machine.MemoryBlock;
  675. heapBlock : Heaps.HeapBlock;
  676. currentMarkValue : LONGINT;
  677. blockAdr : ADDRESS;
  678. mark : LONGINT;
  679. BEGIN
  680. ASSERT(analyzer # NIL);
  681. currentMarkValue := GetCurrentMarkValue();
  682. memBlock := Machine.memBlockHead;
  683. WHILE memBlock # NIL DO
  684. blockAdr := memBlock.beginBlockAdr;
  685. WHILE blockAdr # memBlock.endBlockAdr DO
  686. heapBlock := SYSTEM.VAL(Heaps.HeapBlock, blockAdr + Heaps.BlockHeaderSize); (* get heap block *)
  687. mark := SYSTEM.GET32(blockAdr + Heaps.BlockHeaderSize); (* access to private field heapBlock.mark *)
  688. IF (mark = currentMarkValue) THEN
  689. analyzer.Add(heapBlock, FALSE);
  690. SYSTEM.PUT32(blockAdr + Heaps.BlockHeaderSize, currentMarkValue - 1);
  691. END;
  692. blockAdr := blockAdr + heapBlock.size
  693. END;
  694. memBlock := memBlock.next
  695. END;
  696. SetCurrentMarkValue(currentMarkValue - 1); (* restore Heaps.currentMarkValue *)
  697. END AnalyzeMarkedBlocks;
  698. PROCEDURE WriteType(adr : LONGINT; out : Streams.Writer);
  699. VAR m : Modules.Module; t : Modules.TypeDesc; name: ARRAY 256 OF CHAR;
  700. BEGIN
  701. Modules.ThisTypeByAdr(adr, m, t);
  702. IF m # NIL THEN
  703. out.String(m.name); out.Char(".");
  704. IF (t # NIL) THEN
  705. IF t.name = "" THEN out.String("TYPE") ELSE
  706. COPY(t.name,name);
  707. out.String(name) END
  708. ELSE
  709. out.String("NOTYPEDESC");
  710. END;
  711. ELSE
  712. out.String("NIL")
  713. END
  714. END WriteType;
  715. PROCEDURE GetName(adr: ADDRESS; VAR name: ARRAY OF CHAR);
  716. VAR m : Modules.Module; t : Modules.TypeDesc;
  717. BEGIN
  718. Modules.ThisTypeByAdr(adr, m, t);
  719. name := "";
  720. IF m # NIL THEN
  721. COPY(m.name,name);
  722. IF (t # NIL) THEN
  723. Strings.Append(name,".");
  724. Strings.Append(name,t.name);
  725. END;
  726. END;
  727. END GetName;
  728. (* Access to private field Heaps.currentMarkValue *)
  729. PROCEDURE GetCurrentMarkValue() : LONGINT;
  730. BEGIN
  731. RETURN SYSTEM.GET32(currentMarkValueAddress);
  732. END GetCurrentMarkValue;
  733. PROCEDURE SetCurrentMarkValue(value : LONGINT);
  734. BEGIN
  735. SYSTEM.PUT32(currentMarkValueAddress, value);
  736. END SetCurrentMarkValue;
  737. PROCEDURE IncrementCurrentMarkValue;
  738. BEGIN
  739. SetCurrentMarkValue(GetCurrentMarkValue() + 1);
  740. END IncrementCurrentMarkValue;
  741. PROCEDURE GetCurrentMarkValueAddress() : ADDRESS;
  742. VAR address : ADDRESS; module : Modules.Module; variable : Reflection.Variable;
  743. BEGIN
  744. address := Heaps.NilVal;
  745. module := Modules.ModuleByName("Heaps");
  746. ASSERT(module # NIL);
  747. IF (module # NIL) THEN
  748. IF Reflection.FindVar(module, "currentMarkValue", variable) THEN
  749. (*
  750. ASSERT(variable.n = 1); (* currentMarkValue is not an array *)
  751. ASSERT(variable.type = 6); (*? type is LONGINT, currently no support for 64-bit addresses *)
  752. *)
  753. address := variable.adr;
  754. ELSE HALT(100);
  755. END;
  756. END;
  757. RETURN address;
  758. END GetCurrentMarkValueAddress;
  759. PROCEDURE Terminate;
  760. BEGIN
  761. IF Heaps.allocationLogger = LogAlloc THEN Heaps.SetAllocationLogger(NIL) END;
  762. END Terminate;
  763. BEGIN
  764. currentMarkValueAddress := GetCurrentMarkValueAddress();
  765. ASSERT(currentMarkValueAddress # Heaps.NilVal);
  766. Modules.InstallTermHandler(Terminate);
  767. END Info.
  768. System.Free Info ~
  769. Debugging.DisableGC
  770. Debugging.EnableGC
  771. Compiler.Compile -p=Win32 FoxIntermediateBackend.Mod ~
  772. Info.AllObjects ~
  773. Info.AllObjects * ~
  774. (* view by type *)
  775. Info.AllObjects --sort=0 * ~ sort by none
  776. Info.AllObjects --sort=1 * ~ sort by count
  777. Info.AllObjects --sort=2 * ~ sort by size
  778. Info.AllObjects --sort=3 * ~ sort by total size
  779. Info.AllObjects --sort=4 * ~ sort by name
  780. (* view by allocation pc *)
  781. Info.AllObjects --pc --sort=0 * ~ sort by none
  782. Info.AllObjects --pc --sort=1 * ~ sort by count
  783. Info.AllObjects --pc --sort=2 * ~ sort by size
  784. Info.AllObjects --pc --sort=3 * ~ sort by total size
  785. Info.AllObjects --pc --sort=4 * ~ sort by name
  786. Info.TraceModule PET ~
  787. Info.TraceModule Info ~
  788. Info.TraceModule FoxIntermediateBackend * ~
  789. Info.TraceReference HotKeys.hotkeys ~
  790. Info.TraceReference HotKeys.hotkeys * ~
  791. Info.TraceProcessID 7180 * ~
  792. Info.ModuleDetails -d Modules ~
  793. System.CollectGarbage ~
  794. Compiler.Compile --symbolFilePrefix=/temp/objEO/ --objectFilePrefix=/temp/objEO/ Info.Mod ~
  795. Info.AddAllocatorLogger
  796. Info.RecentAllocators --clear --scale=2400000 ~
  797. Info.RecentAllocators --scale=2400000 ~
  798. Info.RecentAllocators --clear ~
  799. Info.ClearRecentAllocators ~