KernelLog.Mod 9.3 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344
  1. (* Aos, Copyright 2001, Pieter Muller, ETH Zurich *)
  2. MODULE KernelLog; (** AUTHOR "pjm"; PURPOSE "Trace output for booting and debugging"; *)
  3. (* AFI 12.03.2003 - procedure Init modified to obtain trace port info from Aos.Par i.o. being hardcoded. *)
  4. IMPORT SYSTEM, Trace, Machine, Objects;
  5. CONST
  6. BufSize = 8000; (* default trace buffer size (usually overriden by System.StartLog or LogWindow.Open *)
  7. VAR
  8. traceBufDef: ARRAY BufSize OF CHAR; (* default trace buffer *)
  9. traceBufAdr: ADDRESS; traceBufSize: SIZE; (* current trace buffer virtual addresses *)
  10. traceHead, traceTail: ADDRESS;
  11. (** Send the specified characters to the trace output (cf. Streams.Sender). *)
  12. PROCEDURE Send*(CONST buf: ARRAY OF CHAR; ofs, len: LONGINT; propagate: BOOLEAN; VAR res: WORD);
  13. VAR next: ADDRESS; c: CHAR;
  14. BEGIN
  15. INC(len, ofs); (* len is now end position *)
  16. Machine.Acquire(Machine.TraceOutput);
  17. LOOP
  18. IF ofs >= len THEN EXIT END;
  19. c := buf[ofs];
  20. IF c = 0X THEN EXIT END;
  21. next := (traceTail+1) MOD traceBufSize;
  22. IF next # traceHead THEN
  23. SYSTEM.PUT8(traceBufAdr+traceTail, c);
  24. traceTail := next
  25. ELSE (* overwrite previous character with overflow signal *)
  26. SYSTEM.PUT8(traceBufAdr + (traceTail-1) MOD traceBufSize, 3X)
  27. END;
  28. Trace.Char (c);
  29. INC(ofs)
  30. END;
  31. Machine.Release(Machine.TraceOutput)
  32. END Send;
  33. (** Write a string to the trace output. *)
  34. PROCEDURE String*(CONST s: ARRAY OF CHAR);
  35. VAR len, n: SIZE; res: WORD;
  36. BEGIN
  37. len := 0; n := LEN(s);
  38. WHILE (len # n) & (s[len] # 0X) DO INC(len) END;
  39. Send(s, 0, len, FALSE, res)
  40. END String;
  41. (** Skip to the next line on trace output. *)
  42. PROCEDURE Ln*;
  43. BEGIN Char (0DX); Char (0AX);
  44. END Ln;
  45. (** Write a character. *)
  46. PROCEDURE Char*(c: CHAR);
  47. TYPE Str = ARRAY 1 OF CHAR;
  48. BEGIN
  49. String(SYSTEM.VAL(Str, c))
  50. END Char;
  51. (** Write "x" as a decimal number. "w" is the field width. *)
  52. PROCEDURE Int*(x: HUGEINT; w: WORD);
  53. VAR i: SIZE; x0: HUGEINT; a: ARRAY 21 OF CHAR;
  54. BEGIN
  55. IF x < 0 THEN
  56. IF x = MIN(HUGEINT) THEN
  57. DEC(w, 20);
  58. WHILE w > 0 DO Char(" "); DEC(w) END;
  59. String ("-9223372036854775808");
  60. RETURN
  61. ELSE
  62. DEC(w); x0 := -x
  63. END
  64. ELSE
  65. x0 := x
  66. END;
  67. i := 0;
  68. REPEAT
  69. a[i] := CHR(x0 MOD 10 + 30H); x0 := x0 DIV 10; INC(i)
  70. UNTIL x0 = 0;
  71. WHILE w > i DO Char(" "); DEC(w) END;
  72. IF x < 0 THEN Char("-") END;
  73. REPEAT DEC(i); Char(a[i]) UNTIL i = 0
  74. END Int;
  75. PROCEDURE Boolean*(x : BOOLEAN);
  76. BEGIN
  77. IF x THEN String("TRUE") ELSE String("FALSE") END
  78. END Boolean;
  79. (** Write "x" as a decimal number with a power-of-two multiplier (K, M or G), followed by "suffix". "w" is the field width, excluding "suffix". *)
  80. PROCEDURE IntSuffix*(x: HUGEINT; w: WORD; CONST suffix: ARRAY OF CHAR);
  81. CONST K = 1024; M = K*K; G = K*M;
  82. VAR mult: CHAR;
  83. BEGIN
  84. IF x MOD K # 0 THEN
  85. Int(x, w)
  86. ELSE
  87. IF x MOD M # 0 THEN mult := "K"; x := x DIV K
  88. ELSIF x MOD G # 0 THEN mult := "M"; x := x DIV M
  89. ELSE mult := "G"; x := x DIV G
  90. END;
  91. Int(x, w-1); Char(mult)
  92. END;
  93. String(suffix)
  94. END IntSuffix;
  95. (*
  96. (** Write "x" as a hexadecimal number. The absolute value of "w" is the field width. If "w" is negative, two hex digits are printed (x MOD 100H), otherwise 8 digits are printed. *)
  97. PROCEDURE Hex*(x: HUGEINT; w: WORD);
  98. VAR i, j: SIZE; buf: ARRAY 10 OF CHAR;
  99. BEGIN
  100. IF w >= 0 THEN j := 8 ELSE j := 2; w := -w END;
  101. FOR i := j+1 TO w DO Char(" ") END;
  102. FOR i := j-1 TO 0 BY -1 DO
  103. buf[i] := CHR(x MOD 10H + 48);
  104. IF buf[i] > "9" THEN
  105. buf[i] := CHR(ORD(buf[i]) - 48 + 65 - 10)
  106. END;
  107. x := x DIV 10H
  108. END;
  109. buf[j] := 0X;
  110. String(buf)
  111. END Hex;
  112. *)
  113. (** Write an integer in hexadecimal right-justified in a field of at least ABS(w) characters.
  114. If w < 0, the w least significant hex digits of x are written (potentially including leading zeros)
  115. *)
  116. PROCEDURE Hex*( x: HUGEINT; w: WORD );
  117. VAR filler: CHAR; i, maxi, y: WORD; buf: ARRAY 20 OF CHAR;
  118. BEGIN
  119. IF w < 0 THEN filler := '0'; w := -w; maxi := w ELSE filler := ' '; maxi := 16 END;
  120. i := 0;
  121. REPEAT
  122. y := SHORT( x MOD 10H );
  123. IF y < 10 THEN buf[i] := CHR( y + ORD('0') ) ELSE buf[i] := CHR( y - 10 + ORD('A') ) END;
  124. x := x DIV 10H;
  125. INC( i );
  126. UNTIL (x = 0) OR (i = maxi);
  127. WHILE w > i DO Char( filler ); DEC( w ) END;
  128. REPEAT DEC( i ); Char( buf[i] ) UNTIL i = 0
  129. END Hex;
  130. (** Write "x" as a hexadecimal address. *)
  131. PROCEDURE Address* (x: ADDRESS);
  132. BEGIN
  133. Hex(x, -SIZEOF(ADDRESS)*2)
  134. END Address;
  135. (** Write "x" as a size *)
  136. PROCEDURE Size* (x: SIZE);
  137. BEGIN {UNCOOPERATIVE, UNCHECKED}
  138. Int(x,0);
  139. END Size;
  140. (** Write "x" as a hexadecimal number. "w" is the field width. Always prints 16 digits. *)
  141. PROCEDURE HIntHex*(x: HUGEINT; w: WORD);
  142. BEGIN
  143. Hex( x, w )
  144. END HIntHex;
  145. (** Write a block of memory in hex. *)
  146. PROCEDURE Memory*(adr: ADDRESS; size: SIZE);
  147. VAR i, j: ADDRESS; ch: CHAR;
  148. BEGIN
  149. Char(0EX); (* "fixed font" *)
  150. size := adr+size-1;
  151. FOR i := adr TO size BY 16 DO
  152. Address (i); Char (' ');
  153. FOR j := i TO i+15 DO
  154. IF j <= size THEN
  155. SYSTEM.GET(j, ch);
  156. Hex(ORD(ch), -2)
  157. ELSE
  158. String(" ")
  159. END
  160. END;
  161. String(" ");
  162. FOR j := i TO i+15 DO
  163. IF j <= size THEN
  164. SYSTEM.GET(j, ch);
  165. IF (ch < " ") OR (ch >= CHR(127)) THEN ch := "." END;
  166. Char(ch)
  167. END
  168. END;
  169. Ln
  170. END;
  171. Char(0FX) (* "proportional font" *)
  172. END Memory;
  173. (** Write a buffer in hex. *)
  174. PROCEDURE Buffer*(CONST buf: ARRAY OF CHAR; ofs, len: SIZE);
  175. BEGIN
  176. Memory(ADDRESSOF(buf[ofs]), len)
  177. END Buffer;
  178. (** Write bits (ofs..ofs+n-1) of x in binary. *)
  179. PROCEDURE Bits*(x: SET; ofs, n: WORD);
  180. BEGIN
  181. REPEAT
  182. DEC(n);
  183. IF (ofs+n) IN x THEN Char("1") ELSE Char("0") END
  184. UNTIL n = 0
  185. END Bits;
  186. (** write a set as set *)
  187. PROCEDURE Set*(x: SET);
  188. VAR first: BOOLEAN; i: WORD;
  189. BEGIN
  190. first := TRUE;
  191. Char("{");
  192. FOR i := 0 TO MAX(SET) DO
  193. IF i IN x THEN
  194. IF ~first THEN Char(",") ELSE first := FALSE END;
  195. Int(i,1);
  196. END;
  197. END;
  198. Char("}");
  199. END Set;
  200. (** Enter mutually exclusive region for writing, using a fine-grained lock. This region should be kept as short as possible, and only procedures from KernelLog should be called inside it. *)
  201. PROCEDURE Enter*;
  202. BEGIN
  203. Machine.Acquire(Machine.KernelLog);
  204. String("{P cpuid= "); Int(Machine.ID(), 0); String (", pid= "); Int (Objects.GetProcessID (), 0); Char (' ');
  205. END Enter;
  206. (** Exit mutually exclusive region for writing. *)
  207. PROCEDURE Exit*;
  208. BEGIN
  209. Char("}"); Ln;
  210. Machine.Release(Machine.KernelLog)
  211. END Exit;
  212. (* Switch to a new tracing buffer, copying the existing data. *)
  213. PROCEDURE SwitchToBuffer(adr: ADDRESS; size: SIZE);
  214. VAR tail: ADDRESS; c: CHAR;
  215. BEGIN
  216. tail := 0; ASSERT(size > 0);
  217. WHILE (traceHead # traceTail) & (tail+1 # size) DO (* source not empty, destination not full *)
  218. SYSTEM.GET (traceBufAdr + traceHead, c);
  219. SYSTEM.PUT (adr + tail, c);
  220. traceHead := (traceHead+1) MOD traceBufSize;
  221. INC(tail)
  222. END;
  223. traceBufAdr := adr; traceBufSize := size;
  224. traceHead := 0; traceTail := tail
  225. END SwitchToBuffer;
  226. (** Assign a new trace buffer. Used by a display process. *)
  227. PROCEDURE OpenBuffer*(adr: ADDRESS; size: SIZE): BOOLEAN;
  228. VAR ok: BOOLEAN;
  229. BEGIN
  230. Machine.Acquire(Machine.TraceOutput);
  231. IF traceBufAdr = ADDRESSOF(traceBufDef[0]) THEN
  232. SwitchToBuffer(adr, size); ok := TRUE
  233. ELSE
  234. ok := FALSE
  235. END;
  236. Machine.Release(Machine.TraceOutput);
  237. RETURN ok
  238. END OpenBuffer;
  239. (** Return output buffer contents. Used by a display process. *)
  240. PROCEDURE GetBuffer*(VAR val: ARRAY OF CHAR);
  241. VAR i, m: SIZE;
  242. BEGIN
  243. i := 0; m := LEN(val)-1;
  244. Machine.Acquire(Machine.TraceOutput);
  245. WHILE (i < m) & (traceHead # traceTail) DO
  246. val[i] := CHR(SYSTEM.GET8(traceBufAdr + traceHead));
  247. traceHead := (traceHead+1) MOD traceBufSize;
  248. INC(i)
  249. END;
  250. Machine.Release(Machine.TraceOutput);
  251. val[i] := 0X
  252. END GetBuffer;
  253. (** Close the trace buffer and revert to the default. Used by a display process. *)
  254. PROCEDURE CloseBuffer*;
  255. BEGIN
  256. Machine.Acquire(Machine.TraceOutput);
  257. IF traceBufAdr # ADDRESSOF(traceBufDef[0]) THEN
  258. SwitchToBuffer(ADDRESSOF(traceBufDef[0]), LEN(traceBufDef))
  259. END;
  260. Machine.Release(Machine.TraceOutput)
  261. END CloseBuffer;
  262. BEGIN
  263. traceBufAdr := ADDRESSOF(traceBufDef[0]);
  264. traceBufSize := LEN(traceBufDef);
  265. traceHead := 0; traceTail := 0;
  266. END KernelLog.
  267. (**
  268. Notes
  269. This module provides low-level output facilities for Aos. It is similar to the Out module of Oberon, but it can be called from anywhere, even from active object bodies and interrupt handlers. It can write to the text display (when not using a graphics mode), a serial port, a memory buffer, or all of the above. This is controlled by the TraceMode and related config strings (see Aos.Par).
  270. Typically, a memory buffer is used. The buffer is installed by the LogWindow.Open, or with the System.StartLog command when using Oberon. The latter is recommended, as it also interprets traps specially and opens a new viewer for them. The displaying of the buffer is done off-line by the LogWindow or Oberon threads, thereby allowing the procedures here to be called from anywhere.
  271. Control characters:
  272. 0X end of string (can not be printed)
  273. 1X start of trap (if System.StartLog active then trap viewer will be opened and output redirected)
  274. 2X end of trap (if System.StartLog active then it will revert output to the kernel log text)
  275. 3X signal log overflow
  276. 9X TAB (or single space)
  277. 0DX CR (or NL and LF ignored)
  278. 0AX LF (ignored if CR is NL)
  279. 0EX set fixed-width font
  280. 0FX set proportial font (default)
  281. *)
  282. (*
  283. TraceMode:
  284. 0 1 Screen
  285. 2 4 V24
  286. *)
  287. (*
  288. 03.03.1998 pjm First version
  289. 16.06.2000 pjm Cleaned up
  290. 29.11.2000 pjm buffering
  291. 12.06.2001 pjm moved Flags to Traps, moved SegDesc and TSS to AosFragments
  292. *)