KernelLog.Mod 9.3 KB

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