Oberon.Profiler.Mod 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475
  1. MODULE Profiler IN Oberon; (** PRK **)
  2. (*
  3. Statistical Profiler for Aos
  4. author: P.Reali reali@inf.ethz.ch
  5. *)
  6. IMPORT
  7. SYSTEM, Machine IN A2, Modules IN A2, Fonts, Out, Oberon, Texts, Attributes, Objects, Outlines, TextGadgets;
  8. CONST
  9. (* distance between tab positions*)
  10. Identation = 15;
  11. TYPE
  12. Range = POINTER TO RangeDesc;
  13. RangeDesc = RECORD
  14. name: ARRAY 64 OF CHAR;
  15. low, hi: LONGINT;
  16. hits: LONGINT; (*hits inside this range (local and not)*)
  17. locals: LONGINT; (*local hits*)
  18. dsc, next: Range;
  19. END;
  20. LessThanProc = PROCEDURE (a, b: Range): BOOLEAN;
  21. VAR
  22. (*
  23. Trace Format:
  24. [next_trace][ip0][ip1]....[ipn][next_trace][ip0][ip1]....[ipn].......
  25. next_trace points to the next trace in the list.
  26. *)
  27. trace: POINTER TO ARRAY Machine.MaxCPU, 8*1024 OF LONGINT;
  28. tracePos: ARRAY Machine.MaxCPU OF LONGINT;
  29. topM, topP: Range;
  30. pflag, vflag, nflag, tflag: BOOLEAN;
  31. normal, title: Fonts.Font;
  32. tab: ARRAY 32 OF CHAR;
  33. StyleCache: ARRAY 32 OF Objects.Object;
  34. stopBP: ADDRESS;
  35. (* ----------- Sort Routines ---------------- *)
  36. PROCEDURE Sort(list: Range; LessThan: LessThanProc): Range;
  37. VAR res, p, q: Range;
  38. BEGIN
  39. WHILE list # NIL DO
  40. q := list.next;
  41. IF (res = NIL) OR LessThan(list, res) THEN
  42. list.next := res; res := list
  43. ELSE
  44. p := res;
  45. WHILE (p.next#NIL) & LessThan(p.next, list) DO p := p.next END;
  46. list.next := p.next; p.next := list
  47. END;
  48. list := q
  49. END;
  50. RETURN res
  51. END Sort;
  52. PROCEDURE HitsGT(a, b: Range): BOOLEAN;
  53. BEGIN RETURN a.hits > b.hits
  54. END HitsGT;
  55. (* ----------- Output Routines --------------- *)
  56. PROCEDURE CreateStyle(at: LONGINT): Objects.Object;
  57. VAR o: TextGadgets.Style;
  58. BEGIN
  59. IF (at >= LEN(StyleCache)) OR (StyleCache[at] = NIL) THEN
  60. o := TextGadgets.newStyle();
  61. (*
  62. o.width := SHORT(o.width - at*Identation);
  63. *)
  64. o.leftM := SHORT(at*Identation);
  65. Attributes.SetString(o, "Tabs", tab);
  66. IF at < LEN(StyleCache) THEN StyleCache[at] := o END;
  67. RETURN o
  68. ELSE RETURN StyleCache[at]
  69. END;
  70. END CreateStyle;
  71. PROCEDURE Write(VAR w: Texts.Writer; name: ARRAY OF CHAR; cnt, tot: LONGINT);
  72. BEGIN
  73. Texts.WriteString(w, name);
  74. Texts.Write(w, 9X);
  75. Texts.WriteInt(w, cnt, 4); Texts.WriteString(w, " / "); Texts.WriteInt(w, tot, 4);
  76. Texts.WriteLn(w);
  77. END Write;
  78. PROCEDURE DumpHierarchy(top: Range; VAR w: Texts.Writer; level: LONGINT);
  79. (*traverse the structure top and dump the results*)
  80. VAR tw: Texts.Writer; p: Range; outline: Outlines.Outline; sum: LONGINT;
  81. BEGIN
  82. IF top = NIL THEN RETURN END;
  83. Write(w, top.name, top.locals, top.hits);
  84. top.dsc := Sort(top.dsc, HitsGT);
  85. Texts.WriteObj(w, CreateStyle(level+1));
  86. IF top.dsc = NIL THEN
  87. Texts.WriteString(w, "no outgoing calls")
  88. ELSE
  89. p := top.dsc;
  90. WHILE p # NIL DO
  91. INC(sum, p.hits);
  92. Write(w, p.name, p.hits, top.hits); p := p.next;
  93. END;
  94. Write(w, "local", top.locals, top.hits);
  95. Texts.OpenWriter(tw);
  96. Texts.WriteLn(tw);
  97. p := top.dsc;
  98. WHILE p # NIL DO
  99. DumpHierarchy(p, tw, level+1); p := p.next
  100. END;
  101. outline := Outlines.MakeOutline(Outlines.close); Texts.WriteObj(tw, outline);
  102. outline := Outlines.MakeOutline(Outlines.folded);
  103. outline.buf := tw.buf; outline.len := outline.buf.len;
  104. Texts.WriteObj(w, outline)
  105. END;
  106. Texts.WriteObj(w, CreateStyle(level))
  107. END DumpHierarchy;
  108. PROCEDURE DumpList(top: Range; VAR w: Texts.Writer);
  109. VAR p: Range;
  110. BEGIN
  111. IF top = NIL THEN RETURN END;
  112. Write(w, top.name, top.locals, top.hits);
  113. Texts.WriteObj(w, CreateStyle(1));
  114. top.dsc := Sort(top.dsc, HitsGT);
  115. p := top.dsc;
  116. WHILE p # NIL DO
  117. Write(w, p.name, p.locals, p.hits); p := p.next
  118. END;
  119. Texts.WriteObj(w, CreateStyle(0))
  120. END DumpList;
  121. (* ------------- Stack related routines -------------- *)
  122. PROCEDURE FindProcedure(pc: LONGINT; VAR low, hi: LONGINT; VAR name: ARRAY OF CHAR);
  123. (*search a procedure in the reference section of the module*)
  124. VAR i, dummy, refstart, refpos, limit, oldprocstart, procstart: LONGINT; ch: CHAR; mod: Modules.Module;
  125. PROCEDURE ReadNum (VAR pos: LONGINT; VAR i: LONGINT);
  126. VAR n: LONGINT; s: SHORTINT; x: CHAR;
  127. BEGIN
  128. s := 0; n := 0; SYSTEM.GET(pos, x); INC(pos);
  129. WHILE ORD(x) >= 128 DO INC(n, ASH(ORD(x) - 128, s)); INC(s, 7); SYSTEM.GET(pos, x); INC(pos) END;
  130. i := n + ASH(ORD(x) MOD 64 - ORD(x) DIV 64 * 64, s)
  131. END ReadNum;
  132. BEGIN
  133. i := 0;
  134. mod := Modules.ThisModuleByAdr(pc);
  135. WHILE mod.name[i] # 0X DO name[i] := mod.name[i]; INC(i) END;
  136. name[i] := "."; INC(i);
  137. IF (SYSTEM.VAL(LONGINT, mod.refs) # 0) & (LEN(mod.refs) # 0) THEN
  138. refstart := 0; refpos := ADDRESSOF(mod.refs[0]);
  139. procstart := 0;
  140. limit := refpos + LEN(mod.refs);
  141. LOOP
  142. oldprocstart := procstart;
  143. SYSTEM.GET(refpos, ch); INC(refpos);
  144. IF refpos >= limit THEN procstart := LEN(mod.code); EXIT END;
  145. IF ch = 0F8X THEN (* start proc *)
  146. ReadNum(refpos, procstart);
  147. IF pc < ADDRESSOF(mod.code[0]) + procstart THEN EXIT END;
  148. refstart := refpos;
  149. REPEAT SYSTEM.GET(refpos, ch); INC(refpos) UNTIL ch = 0X; (*skip name*)
  150. ELSIF ch = 0F9X THEN (*proc, new format*)
  151. ReadNum(refpos, procstart);
  152. IF pc < ADDRESSOF(mod.code[0]) + procstart THEN EXIT END;
  153. INC(refpos, 1+1+1+1);
  154. refstart := refpos;
  155. REPEAT SYSTEM.GET(refpos, ch); INC(refpos) UNTIL ch = 0X; (*skip name*)
  156. ELSIF ch < 0F8X THEN (* skip object *)
  157. INC(refpos); (* skip typeform *)
  158. ReadNum(refpos, dummy); (* skip offset *)
  159. REPEAT SYSTEM.GET(refpos, ch); INC(refpos) UNTIL ch = 0X; (*skip name*)
  160. END
  161. END;
  162. refpos := refstart;
  163. IF refpos # 0 THEN
  164. SYSTEM.GET(refpos, ch); INC(refpos);
  165. WHILE ch # 0X DO name[i] := ch; INC(i); SYSTEM.GET(refpos, ch); INC(refpos) END;
  166. name[i] := 0X;
  167. low := ADDRESSOF(mod.code[0]) + oldprocstart;
  168. hi := ADDRESSOF(mod.code[0]) + procstart;
  169. END
  170. END
  171. END FindProcedure;
  172. PROCEDURE Init(top: Range; pc: LONGINT; proc: BOOLEAN);
  173. VAR m: Modules.Module;
  174. BEGIN
  175. IF pc = 0 THEN
  176. (*skip*)
  177. ELSIF proc THEN
  178. FindProcedure(pc, top.low, top.hi, top.name);
  179. ASSERT(top.low <= pc);
  180. ASSERT(pc < top.hi);
  181. ELSE
  182. m := Modules.ThisModuleByAdr(pc);
  183. COPY(m.name, top.name);
  184. top.low := ADDRESSOF(m.code[0]);
  185. top.hi := top.low + LEN(m.code);
  186. END;
  187. END Init;
  188. PROCEDURE Find(top: Range; pc: LONGINT; proc: BOOLEAN): Range;
  189. (*Find/Insert an entry in the list*)
  190. VAR p, q: Range;
  191. BEGIN
  192. p := top.dsc;
  193. IF (p=NIL) OR (pc < p.low) THEN
  194. NEW(q); Init(q, pc, proc); q.next := top.dsc; top.dsc := q;
  195. RETURN q
  196. ELSE
  197. WHILE (p.next # NIL) & (p.next.low <= pc) DO p := p.next END;
  198. IF (pc > p.hi) THEN
  199. NEW(q); Init(q, pc, proc); q.next := p.next; p.next := q;
  200. RETURN q
  201. ELSE
  202. RETURN p
  203. END
  204. END
  205. END Find;
  206. PROCEDURE Analyze;
  207. VAR p, q: Range; pc, pos, next, i: LONGINT;
  208. BEGIN
  209. FOR i := 0 TO Machine.MaxCPU - 1 DO
  210. next := 0;
  211. WHILE next < tracePos[i] DO
  212. pos := trace[i][next]-1; p := topM; q := topP;
  213. WHILE pos > next DO
  214. pc := trace[i][pos];
  215. (*trace modules*)
  216. IF (pc < p.low) OR (pc >= p.hi) THEN p := Find(p, pc, FALSE); INC(p.hits) END;
  217. (*trace procedures*)
  218. q := Find(q, pc, TRUE); INC(q.hits);
  219. DEC(pos)
  220. END;
  221. INC(p.locals);
  222. INC(q.locals);
  223. next := trace[i][next];
  224. END
  225. END
  226. END Analyze;
  227. PROCEDURE DumpTrace*;
  228. VAR pc, pos, next, i: LONGINT; low, hi: LONGINT; name: ARRAY 64 OF CHAR; W: Texts.Writer; t: Texts.Text;
  229. BEGIN
  230. Texts.OpenWriter(W);
  231. Texts.SetFont(W, Fonts.This("Courier10.Scn.Fnt"));
  232. FOR i := 0 TO Machine.MaxCPU - 1 DO
  233. next := 0;
  234. WHILE next < tracePos[i] DO
  235. Texts.WriteInt(W, next, 4); Texts.WriteString(W, " ------------------"); Texts.WriteLn(W);
  236. pos := next+1;
  237. next := trace[i][next];
  238. WHILE pos < next DO
  239. pc := trace[i][pos];
  240. FindProcedure(pc, low, hi, name);
  241. Texts.WriteInt(W, pos, 4); Texts.WriteString(W, " ");
  242. Texts.WriteHex(W, pc); Texts.WriteHex(W, low); Texts.WriteHex(W, hi);
  243. Texts.WriteString(W, " "); Texts.WriteString(W, name);
  244. Texts.WriteLn(W);
  245. INC(pos)
  246. END;
  247. END
  248. END;
  249. NEW(t); Texts.Open(t, ""); Texts.Append(t, W.buf); Oberon.OpenText("", t, 640, 400);
  250. END DumpTrace;
  251. PROCEDURE CollectOverview(root: Range): Range;
  252. VAR l, p, next, next2, res: Range;
  253. BEGIN
  254. res := NIL;
  255. WHILE root # NIL DO
  256. next := root.next;
  257. l := CollectOverview(root.dsc);
  258. root.dsc := NIL;
  259. (* if this range is already present in the overview of the subtree, the cumulated count should be ignored (don't count range twice) *)
  260. p := l;
  261. WHILE (p # NIL) & (p.low # root.low) DO p := p.next END;
  262. IF p # NIL THEN
  263. INC(p.locals, root.locals); (*add count, discard root*)
  264. p.hits := root.hits
  265. ELSE
  266. root.next := l; (*add root to overview*)
  267. l := root;
  268. END;
  269. (*merge step*)
  270. WHILE l # NIL DO
  271. p := res; next2 := l.next;
  272. WHILE (p # NIL) & (p.low # l.low) DO p := p.next END;
  273. IF p # NIL THEN
  274. INC(p.locals, l.locals);
  275. INC(p.hits, l.hits)
  276. ELSE
  277. l.next := res;
  278. res := l
  279. END;
  280. l := next2
  281. END;
  282. root := next
  283. END;
  284. RETURN res
  285. END CollectOverview;
  286. PROCEDURE Output(call: ARRAY OF CHAR; times, use: LONGINT);
  287. VAR t: Texts.Text; w: Texts.Writer; i: LONGINT;
  288. BEGIN
  289. i := 0; WHILE i < LEN(StyleCache) DO StyleCache[i] := NIL; INC(i) END;
  290. Texts.OpenWriter(w);
  291. Texts.WriteString(w, "Profiling ["); Texts.WriteString(w, call); Texts.WriteString(w, "]x");
  292. Texts.WriteInt(w, times,0); Texts.WriteLn(w); Texts.WriteLn(w);
  293. Texts.WriteString(w, "Trace Array usage: "); Texts.WriteRealFix(w, 100* use / LEN(trace, 1), 5, 2, 0);
  294. Texts.WriteLn(w); Texts.WriteLn(w);
  295. Texts.SetFont(w, title); Texts.WriteString(w, "Trace of the module calls"); Texts.SetFont(w, normal); Texts.WriteLn(w);
  296. StyleCache[1] := NIL; (* Hack!! *)
  297. tab := "120, 170";
  298. DumpHierarchy(topM, w, 0); Texts.WriteLn(w);
  299. Texts.SetFont(w, title); Texts.WriteString(w, "Overview of the involved modules"); Texts.SetFont(w, normal); Texts.WriteLn(w);
  300. topM.dsc := CollectOverview(topM.dsc);
  301. DumpList(topM, w); Texts.WriteLn(w);
  302. Texts.SetFont(w, title); Texts.WriteString(w, "Trace of the procedure calls"); Texts.SetFont(w, normal); Texts.WriteLn(w);
  303. StyleCache[1] := NIL; (* Hack!! *)
  304. tab := "180, 230";
  305. DumpHierarchy(topP, w, 0); Texts.WriteLn(w);
  306. Texts.SetFont(w, title); Texts.WriteString(w, "Overview of the involved procedures"); Texts.SetFont(w, normal); Texts.WriteLn(w);
  307. topP.dsc := CollectOverview(topP.dsc);
  308. DumpList(topP, w); Texts.WriteLn(w);
  309. NEW(t); Texts.Open(t, ""); Texts.Append(t, w.buf);
  310. Oberon.OpenText("", t, 640, 400);
  311. topP := NIL; topM := NIL
  312. END Output;
  313. PROCEDURE HandleTimer(id: LONGINT; CONST state: Machine.State);
  314. VAR pc, bp: ADDRESS; cnt, pos: LONGINT;
  315. BEGIN
  316. pos := tracePos[id];
  317. pc := state.PC; bp := state.BP;
  318. cnt :=pos; INC(pos);
  319. WHILE (pos < LEN(trace, 1)) & (bp # 0) & (bp # stopBP) DO
  320. trace[id][pos] := pc; SYSTEM.GET(bp+SIZEOF(ADDRESS), pc); SYSTEM.GET(bp, bp); INC(pos)
  321. END;
  322. IF (pos < LEN(trace, 1)) & (bp = stopBP) THEN trace[id][cnt] := pos ELSE pos := cnt END;
  323. tracePos[id] := pos
  324. END HandleTimer;
  325. (** Profile [repetitions] M.P params ~
  326. default repetitions = 1
  327. *)
  328. PROCEDURE Profile*;
  329. VAR times, n, max, i: LONGINT; s: Texts.Scanner; call: ARRAY 256 OF CHAR;
  330. res: INTEGER;
  331. BEGIN
  332. (*parse parameters*)
  333. Texts.OpenScanner(s, Oberon.Par.text, Oberon.Par.pos); Texts.Scan(s);
  334. IF s.class = Texts.Int THEN times := s.i; Texts.Scan(s) ELSE times := 1 END;
  335. nflag := FALSE; pflag := FALSE; vflag := FALSE; tflag := FALSE;
  336. COPY(s.s, call); n := 0;
  337. WHILE (s.s[n]#0X) & (s.s[n]#".") DO INC(n) END;
  338. s.s[n] := 0X;
  339. NEW(topM);
  340. NEW(topP);
  341. Oberon.Par.pos := Texts.Pos(s);
  342. (* perform *)
  343. max := 0; n := times;
  344. stopBP := SYSTEM.GetFramePointer ();
  345. WHILE n > 0 DO
  346. FOR i := 0 TO Machine.MaxCPU-1 DO tracePos[i] := 0 END;
  347. Machine.InstallEventHandler(HandleTimer);
  348. Oberon.Call(call, Oberon.Par, FALSE, res);
  349. Machine.InstallEventHandler(NIL);
  350. DEC(n);
  351. FOR i := 0 TO Machine.MaxCPU-1 DO
  352. IF tracePos[i] > max THEN max := tracePos[i] END;
  353. IF tracePos[i] > LEN(trace, 1)-20 THEN
  354. Out.String("trace array was too small!!!!"); Out.Ln;
  355. END;
  356. END;
  357. Analyze
  358. END;
  359. topM := topM.dsc; (*skip self *)
  360. topP := topP.dsc;
  361. Output(call, times, max);
  362. END Profile;
  363. PROCEDURE Start*;
  364. VAR i: LONGINT;
  365. BEGIN
  366. NEW(topM); topM.low := 0; topM.hi := 0; topM.name := "huga";
  367. NEW(topP); topP.low := 0; topP.hi := 0; topP.name := "huga";
  368. FOR i := 0 TO Machine.MaxCPU-1 DO tracePos[i] := 0 END;
  369. stopBP := 0;
  370. Machine.InstallEventHandler(HandleTimer);
  371. END Start;
  372. PROCEDURE Stop*;
  373. VAR i, max: LONGINT;
  374. BEGIN
  375. Machine.InstallEventHandler(NIL);
  376. FOR i := 0 TO Machine.MaxCPU-1 DO
  377. IF tracePos[i] > max THEN max := tracePos[i] END;
  378. END;
  379. IF max > LEN(trace, 1)-20 THEN Out.String("trace array was too small!!!!"); Out.Ln END;
  380. Analyze;
  381. (*
  382. topM := topM.dsc;
  383. topP := topP.dsc;
  384. *)
  385. Output("continuous", 0, max);
  386. END Stop;
  387. PROCEDURE Dummy*;
  388. VAR o: Objects.Object;
  389. BEGIN
  390. (*Output("", 0, 0);*)
  391. o := CreateStyle(1);
  392. END Dummy;
  393. PROCEDURE Dummy2*;
  394. VAR i: LONGINT;
  395. BEGIN
  396. FOR i := 0 TO 20 DO
  397. Out.Int(i, 0); Out.Ln
  398. END
  399. END Dummy2;
  400. BEGIN
  401. normal := Fonts.This("Oberon10.Scn.Fnt"); title := Fonts.This("Oberon12b.Scn.Fnt");
  402. NEW(trace);
  403. END Profiler.
  404. Profiler.Profile Compiler.Compile * ~
  405. Profiler.Profile 5 Compiler.Compile Profiler.Mod ~
  406. Profiler.Profile 20 Profiler.Dummy ~
  407. Profiler.Profile 20000 Profiler.Dummy ~
  408. Profiler.Profile 20 System.Time ~
  409. Profiler.Profile System.Time ~
  410. Profiler.DumpTrace
  411. Profiler.Reset
  412. Profiler.Test
  413. Profiler.Profile 10 Compiler.Compile Profiler.Mod ~
  414. System.State Profiler ~
  415. System.Free Profiler ~
  416. System.Watch
  417. Configuration.DoCommands
  418. Profiler.Start
  419. System.Time
  420. System.Time
  421. Profiler.Stop
  422. ~