dump.lua 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647
  1. ----------------------------------------------------------------------------
  2. -- LuaJIT compiler dump module.
  3. --
  4. -- Copyright (C) 2005-2011 Mike Pall. All rights reserved.
  5. -- Released under the MIT license. See Copyright Notice in luajit.h
  6. ----------------------------------------------------------------------------
  7. --
  8. -- This module can be used to debug the JIT compiler itself. It dumps the
  9. -- code representations and structures used in various compiler stages.
  10. --
  11. -- Example usage:
  12. --
  13. -- luajit -jdump -e "local x=0; for i=1,1e6 do x=x+i end; print(x)"
  14. -- luajit -jdump=im -e "for i=1,1000 do for j=1,1000 do end end" | less -R
  15. -- luajit -jdump=is myapp.lua | less -R
  16. -- luajit -jdump=-b myapp.lua
  17. -- luajit -jdump=+aH,myapp.html myapp.lua
  18. -- luajit -jdump=ixT,myapp.dump myapp.lua
  19. --
  20. -- The first argument specifies the dump mode. The second argument gives
  21. -- the output file name. Default output is to stdout, unless the environment
  22. -- variable LUAJIT_DUMPFILE is set. The file is overwritten every time the
  23. -- module is started.
  24. --
  25. -- Different features can be turned on or off with the dump mode. If the
  26. -- mode starts with a '+', the following features are added to the default
  27. -- set of features; a '-' removes them. Otherwise the features are replaced.
  28. --
  29. -- The following dump features are available (* marks the default):
  30. --
  31. -- * t Print a line for each started, ended or aborted trace (see also -jv).
  32. -- * b Dump the traced bytecode.
  33. -- * i Dump the IR (intermediate representation).
  34. -- r Augment the IR with register/stack slots.
  35. -- s Dump the snapshot map.
  36. -- * m Dump the generated machine code.
  37. -- x Print each taken trace exit.
  38. -- X Print each taken trace exit and the contents of all registers.
  39. --
  40. -- The output format can be set with the following characters:
  41. --
  42. -- T Plain text output.
  43. -- A ANSI-colored text output
  44. -- H Colorized HTML + CSS output.
  45. --
  46. -- The default output format is plain text. It's set to ANSI-colored text
  47. -- if the COLORTERM variable is set. Note: this is independent of any output
  48. -- redirection, which is actually considered a feature.
  49. --
  50. -- You probably want to use less -R to enjoy viewing ANSI-colored text from
  51. -- a pipe or a file. Add this to your ~/.bashrc: export LESS="-R"
  52. --
  53. ------------------------------------------------------------------------------
  54. -- Cache some library functions and objects.
  55. local jit = require("jit")
  56. assert(jit.version_num == 20000, "LuaJIT core/library version mismatch")
  57. local jutil = require("jit.util")
  58. local vmdef = require("jit.vmdef")
  59. local funcinfo, funcbc = jutil.funcinfo, jutil.funcbc
  60. local traceinfo, traceir, tracek = jutil.traceinfo, jutil.traceir, jutil.tracek
  61. local tracemc, tracesnap = jutil.tracemc, jutil.tracesnap
  62. local traceexitstub, ircalladdr = jutil.traceexitstub, jutil.ircalladdr
  63. local bit = require("bit")
  64. local band, shl, shr = bit.band, bit.lshift, bit.rshift
  65. local sub, gsub, format = string.sub, string.gsub, string.format
  66. local byte, char, rep = string.byte, string.char, string.rep
  67. local type, tostring = type, tostring
  68. local stdout, stderr = io.stdout, io.stderr
  69. -- Load other modules on-demand.
  70. local bcline, disass
  71. -- Active flag, output file handle and dump mode.
  72. local active, out, dumpmode
  73. ------------------------------------------------------------------------------
  74. local symtab = {}
  75. local nexitsym = 0
  76. -- Fill symbol table with trace exit addresses.
  77. local function fillsymtab(nexit)
  78. local t = symtab
  79. if nexitsym == 0 then
  80. local ircall = vmdef.ircall
  81. for i=0,#ircall do
  82. local addr = ircalladdr(i)
  83. if addr ~= 0 then t[addr] = ircall[i] end
  84. end
  85. end
  86. if nexit > nexitsym then
  87. for i=nexitsym,nexit-1 do
  88. local addr = traceexitstub(i)
  89. if addr == nil then nexit = 1000000; break end
  90. t[addr] = tostring(i)
  91. end
  92. nexitsym = nexit
  93. end
  94. return t
  95. end
  96. local function dumpwrite(s)
  97. out:write(s)
  98. end
  99. -- Disassemble machine code.
  100. local function dump_mcode(tr)
  101. local info = traceinfo(tr)
  102. if not info then return end
  103. local mcode, addr, loop = tracemc(tr)
  104. if not mcode then return end
  105. if not disass then disass = require("jit.dis_"..jit.arch) end
  106. out:write("---- TRACE ", tr, " mcode ", #mcode, "\n")
  107. local ctx = disass.create(mcode, addr, dumpwrite)
  108. ctx.hexdump = 0
  109. ctx.symtab = fillsymtab(info.nexit)
  110. if loop ~= 0 then
  111. symtab[addr+loop] = "LOOP"
  112. ctx:disass(0, loop)
  113. out:write("->LOOP:\n")
  114. ctx:disass(loop, #mcode-loop)
  115. symtab[addr+loop] = nil
  116. else
  117. ctx:disass(0, #mcode)
  118. end
  119. end
  120. ------------------------------------------------------------------------------
  121. local irtype_text = {
  122. [0] = "nil",
  123. "fal",
  124. "tru",
  125. "lud",
  126. "str",
  127. "p32",
  128. "thr",
  129. "pro",
  130. "fun",
  131. "p64",
  132. "cdt",
  133. "tab",
  134. "udt",
  135. "flt",
  136. "num",
  137. "i8 ",
  138. "u8 ",
  139. "i16",
  140. "u16",
  141. "int",
  142. "u32",
  143. "i64",
  144. "u64",
  145. "sfp",
  146. }
  147. local colortype_ansi = {
  148. [0] = "%s",
  149. "%s",
  150. "%s",
  151. "\027[36m%s\027[m",
  152. "\027[32m%s\027[m",
  153. "%s",
  154. "\027[1m%s\027[m",
  155. "%s",
  156. "\027[1m%s\027[m",
  157. "%s",
  158. "\027[33m%s\027[m",
  159. "\027[31m%s\027[m",
  160. "\027[36m%s\027[m",
  161. "\027[34m%s\027[m",
  162. "\027[34m%s\027[m",
  163. "\027[35m%s\027[m",
  164. "\027[35m%s\027[m",
  165. "\027[35m%s\027[m",
  166. "\027[35m%s\027[m",
  167. "\027[35m%s\027[m",
  168. "\027[35m%s\027[m",
  169. "\027[35m%s\027[m",
  170. "\027[35m%s\027[m",
  171. "\027[35m%s\027[m",
  172. }
  173. local function colorize_text(s, t)
  174. return s
  175. end
  176. local function colorize_ansi(s, t)
  177. return format(colortype_ansi[t], s)
  178. end
  179. local irtype_ansi = setmetatable({},
  180. { __index = function(tab, t)
  181. local s = colorize_ansi(irtype_text[t], t); tab[t] = s; return s; end })
  182. local html_escape = { ["<"] = "&lt;", [">"] = "&gt;", ["&"] = "&amp;", }
  183. local function colorize_html(s, t)
  184. s = gsub(s, "[<>&]", html_escape)
  185. return format('<span class="irt_%s">%s</span>', irtype_text[t], s)
  186. end
  187. local irtype_html = setmetatable({},
  188. { __index = function(tab, t)
  189. local s = colorize_html(irtype_text[t], t); tab[t] = s; return s; end })
  190. local header_html = [[
  191. <style type="text/css">
  192. background { background: #ffffff; color: #000000; }
  193. pre.ljdump {
  194. font-size: 10pt;
  195. background: #f0f4ff;
  196. color: #000000;
  197. border: 1px solid #bfcfff;
  198. padding: 0.5em;
  199. margin-left: 2em;
  200. margin-right: 2em;
  201. }
  202. span.irt_str { color: #00a000; }
  203. span.irt_thr, span.irt_fun { color: #404040; font-weight: bold; }
  204. span.irt_tab { color: #c00000; }
  205. span.irt_udt, span.irt_lud { color: #00c0c0; }
  206. span.irt_num { color: #4040c0; }
  207. span.irt_int, span.irt_i8, span.irt_u8, span.irt_i16, span.irt_u16 { color: #b040b0; }
  208. </style>
  209. ]]
  210. local colorize, irtype
  211. -- Lookup tables to convert some literals into names.
  212. local litname = {
  213. ["SLOAD "] = setmetatable({}, { __index = function(t, mode)
  214. local s = ""
  215. if band(mode, 1) ~= 0 then s = s.."P" end
  216. if band(mode, 2) ~= 0 then s = s.."F" end
  217. if band(mode, 4) ~= 0 then s = s.."T" end
  218. if band(mode, 8) ~= 0 then s = s.."C" end
  219. if band(mode, 16) ~= 0 then s = s.."R" end
  220. if band(mode, 32) ~= 0 then s = s.."I" end
  221. t[mode] = s
  222. return s
  223. end}),
  224. ["XLOAD "] = { [0] = "", "R", "V", "RV", "U", "RU", "VU", "RVU", },
  225. ["CONV "] = setmetatable({}, { __index = function(t, mode)
  226. local s = irtype[band(mode, 31)]
  227. s = irtype[band(shr(mode, 5), 31)].."."..s
  228. if band(mode, 0x400) ~= 0 then s = s.." trunc"
  229. elseif band(mode, 0x800) ~= 0 then s = s.." sext" end
  230. local c = shr(mode, 14)
  231. if c == 2 then s = s.." index" elseif c == 3 then s = s.." check" end
  232. t[mode] = s
  233. return s
  234. end}),
  235. ["FLOAD "] = vmdef.irfield,
  236. ["FREF "] = vmdef.irfield,
  237. ["FPMATH"] = vmdef.irfpm,
  238. }
  239. local function ctlsub(c)
  240. if c == "\n" then return "\\n"
  241. elseif c == "\r" then return "\\r"
  242. elseif c == "\t" then return "\\t"
  243. elseif c == "\r" then return "\\r"
  244. else return format("\\%03d", byte(c))
  245. end
  246. end
  247. local function fmtfunc(func, pc)
  248. local fi = funcinfo(func, pc)
  249. if fi.loc then
  250. return fi.loc
  251. elseif fi.ffid then
  252. return vmdef.ffnames[fi.ffid]
  253. elseif fi.addr then
  254. return format("C:%x", fi.addr)
  255. else
  256. return "(?)"
  257. end
  258. end
  259. local function formatk(tr, idx)
  260. local k, t, slot = tracek(tr, idx)
  261. local tn = type(k)
  262. local s
  263. if tn == "number" then
  264. if k == 2^52+2^51 then
  265. s = "bias"
  266. else
  267. s = format("%+.14g", k)
  268. end
  269. elseif tn == "string" then
  270. s = format(#k > 20 and '"%.20s"~' or '"%s"', gsub(k, "%c", ctlsub))
  271. elseif tn == "function" then
  272. s = fmtfunc(k)
  273. elseif tn == "table" then
  274. s = format("{%p}", k)
  275. elseif tn == "userdata" then
  276. if t == 12 then
  277. s = format("userdata:%p", k)
  278. else
  279. s = format("[%p]", k)
  280. if s == "[0x00000000]" then s = "NULL" end
  281. end
  282. elseif t == 21 then -- int64_t
  283. s = sub(tostring(k), 1, -3)
  284. if sub(s, 1, 1) ~= "-" then s = "+"..s end
  285. else
  286. s = tostring(k) -- For primitives.
  287. end
  288. s = colorize(format("%-4s", s), t)
  289. if slot then
  290. s = format("%s @%d", s, slot)
  291. end
  292. return s
  293. end
  294. local function printsnap(tr, snap)
  295. local n = 2
  296. for s=0,snap[1]-1 do
  297. local sn = snap[n]
  298. if shr(sn, 24) == s then
  299. n = n + 1
  300. local ref = band(sn, 0xffff) - 0x8000 -- REF_BIAS
  301. if ref < 0 then
  302. out:write(formatk(tr, ref))
  303. elseif band(sn, 0x80000) ~= 0 then -- SNAP_SOFTFPNUM
  304. out:write(colorize(format("%04d/%04d", ref, ref+1), 14))
  305. else
  306. local m, ot, op1, op2 = traceir(tr, ref)
  307. out:write(colorize(format("%04d", ref), band(ot, 31)))
  308. end
  309. out:write(band(sn, 0x10000) == 0 and " " or "|") -- SNAP_FRAME
  310. else
  311. out:write("---- ")
  312. end
  313. end
  314. out:write("]\n")
  315. end
  316. -- Dump snapshots (not interleaved with IR).
  317. local function dump_snap(tr)
  318. out:write("---- TRACE ", tr, " snapshots\n")
  319. for i=0,1000000000 do
  320. local snap = tracesnap(tr, i)
  321. if not snap then break end
  322. out:write(format("#%-3d %04d [ ", i, snap[0]))
  323. printsnap(tr, snap)
  324. end
  325. end
  326. -- Return a register name or stack slot for a rid/sp location.
  327. local function ridsp_name(ridsp)
  328. if not disass then disass = require("jit.dis_"..jit.arch) end
  329. local rid = band(ridsp, 0xff)
  330. if ridsp > 255 then return format("[%x]", shr(ridsp, 8)*4) end
  331. if rid < 128 then return disass.regname(rid) end
  332. return ""
  333. end
  334. -- Recursively gather CALL* args and dump them.
  335. local function dumpcallargs(tr, ins)
  336. if ins < 0 then
  337. out:write(formatk(tr, ins))
  338. else
  339. local m, ot, op1, op2 = traceir(tr, ins)
  340. local oidx = 6*shr(ot, 8)
  341. local op = sub(vmdef.irnames, oidx+1, oidx+6)
  342. if op == "CARG " then
  343. dumpcallargs(tr, op1)
  344. if op2 < 0 then
  345. out:write(" ", formatk(tr, op2))
  346. else
  347. out:write(" ", format("%04d", op2))
  348. end
  349. else
  350. out:write(format("%04d", ins))
  351. end
  352. end
  353. end
  354. -- Dump IR and interleaved snapshots.
  355. local function dump_ir(tr, dumpsnap, dumpreg)
  356. local info = traceinfo(tr)
  357. if not info then return end
  358. local nins = info.nins
  359. out:write("---- TRACE ", tr, " IR\n")
  360. local irnames = vmdef.irnames
  361. local snapref = 65536
  362. local snap, snapno
  363. if dumpsnap then
  364. snap = tracesnap(tr, 0)
  365. snapref = snap[0]
  366. snapno = 0
  367. end
  368. for ins=1,nins do
  369. if ins >= snapref then
  370. if dumpreg then
  371. out:write(format(".... SNAP #%-3d [ ", snapno))
  372. else
  373. out:write(format(".... SNAP #%-3d [ ", snapno))
  374. end
  375. printsnap(tr, snap)
  376. snapno = snapno + 1
  377. snap = tracesnap(tr, snapno)
  378. snapref = snap and snap[0] or 65536
  379. end
  380. local m, ot, op1, op2, ridsp = traceir(tr, ins)
  381. local oidx, t = 6*shr(ot, 8), band(ot, 31)
  382. local op = sub(irnames, oidx+1, oidx+6)
  383. if op == "LOOP " then
  384. if dumpreg then
  385. out:write(format("%04d ------------ LOOP ------------\n", ins))
  386. else
  387. out:write(format("%04d ------ LOOP ------------\n", ins))
  388. end
  389. elseif op ~= "NOP " and op ~= "CARG " and
  390. (dumpreg or op ~= "RENAME") then
  391. if dumpreg then
  392. out:write(format("%04d %-5s ", ins, ridsp_name(ridsp)))
  393. else
  394. out:write(format("%04d ", ins))
  395. end
  396. out:write(format("%s%s %s %s ",
  397. band(ot, 128) == 0 and " " or ">",
  398. band(ot, 64) == 0 and " " or "+",
  399. irtype[t], op))
  400. local m1, m2 = band(m, 3), band(m, 3*4)
  401. if sub(op, 1, 4) == "CALL" then
  402. if m2 == 1*4 then -- op2 == IRMlit
  403. out:write(format("%-10s (", vmdef.ircall[op2]))
  404. elseif op2 < 0 then
  405. out:write(format("[0x%x](", tonumber((tracek(tr, op2)))))
  406. else
  407. out:write(format("%04d (", op2))
  408. end
  409. if op1 ~= -1 then dumpcallargs(tr, op1) end
  410. out:write(")")
  411. elseif op == "CNEW " and op2 == -1 then
  412. out:write(formatk(tr, op1))
  413. elseif m1 ~= 3 then -- op1 != IRMnone
  414. if op1 < 0 then
  415. out:write(formatk(tr, op1))
  416. else
  417. out:write(format(m1 == 0 and "%04d" or "#%-3d", op1))
  418. end
  419. if m2 ~= 3*4 then -- op2 != IRMnone
  420. if m2 == 1*4 then -- op2 == IRMlit
  421. local litn = litname[op]
  422. if litn and litn[op2] then
  423. out:write(" ", litn[op2])
  424. elseif op == "UREFO " or op == "UREFC " then
  425. out:write(format(" #%-3d", shr(op2, 8)))
  426. else
  427. out:write(format(" #%-3d", op2))
  428. end
  429. elseif op2 < 0 then
  430. out:write(" ", formatk(tr, op2))
  431. else
  432. out:write(format(" %04d", op2))
  433. end
  434. end
  435. end
  436. out:write("\n")
  437. end
  438. end
  439. if snap then
  440. if dumpreg then
  441. out:write(format(".... SNAP #%-3d [ ", snapno))
  442. else
  443. out:write(format(".... SNAP #%-3d [ ", snapno))
  444. end
  445. printsnap(tr, snap)
  446. end
  447. end
  448. ------------------------------------------------------------------------------
  449. local recprefix = ""
  450. local recdepth = 0
  451. -- Format trace error message.
  452. local function fmterr(err, info)
  453. if type(err) == "number" then
  454. if type(info) == "function" then info = fmtfunc(info) end
  455. err = format(vmdef.traceerr[err], info)
  456. end
  457. return err
  458. end
  459. -- Dump trace states.
  460. local function dump_trace(what, tr, func, pc, otr, oex)
  461. if what == "stop" or (what == "abort" and dumpmode.a) then
  462. if dumpmode.i then dump_ir(tr, dumpmode.s, dumpmode.r and what == "stop")
  463. elseif dumpmode.s then dump_snap(tr) end
  464. if dumpmode.m then dump_mcode(tr) end
  465. end
  466. if what == "start" then
  467. if dumpmode.H then out:write('<pre class="ljdump">\n') end
  468. out:write("---- TRACE ", tr, " ", what)
  469. if otr then out:write(" ", otr, "/", oex) end
  470. out:write(" ", fmtfunc(func, pc), "\n")
  471. recprefix = ""
  472. elseif what == "stop" or what == "abort" then
  473. out:write("---- TRACE ", tr, " ", what)
  474. recprefix = nil
  475. if what == "abort" then
  476. out:write(" ", fmtfunc(func, pc), " -- ", fmterr(otr, oex), "\n")
  477. else
  478. local info = traceinfo(tr)
  479. local link, ltype = info.link, info.linktype
  480. if link == tr or link == 0 then
  481. out:write(" -> ", ltype, "\n")
  482. elseif ltype == "root" then
  483. out:write(" -> ", link, "\n")
  484. else
  485. out:write(" -> ", link, " ", ltype, "\n")
  486. end
  487. end
  488. if dumpmode.H then out:write("</pre>\n\n") else out:write("\n") end
  489. else
  490. out:write("---- TRACE ", what, "\n\n")
  491. end
  492. out:flush()
  493. end
  494. -- Dump recorded bytecode.
  495. local function dump_record(tr, func, pc, depth, callee)
  496. if depth ~= recdepth then
  497. recdepth = depth
  498. recprefix = rep(" .", depth)
  499. end
  500. local line
  501. if pc >= 0 then
  502. line = bcline(func, pc, recprefix)
  503. if dumpmode.H then line = gsub(line, "[<>&]", html_escape) end
  504. else
  505. line = "0000 "..recprefix.." FUNCC \n"
  506. callee = func
  507. end
  508. if pc <= 0 then
  509. out:write(sub(line, 1, -2), " ; ", fmtfunc(func), "\n")
  510. else
  511. out:write(line)
  512. end
  513. if pc >= 0 and band(funcbc(func, pc), 0xff) < 16 then -- ORDER BC
  514. out:write(bcline(func, pc+1, recprefix)) -- Write JMP for cond.
  515. end
  516. end
  517. ------------------------------------------------------------------------------
  518. -- Dump taken trace exits.
  519. local function dump_texit(tr, ex, ngpr, nfpr, ...)
  520. out:write("---- TRACE ", tr, " exit ", ex, "\n")
  521. if dumpmode.X then
  522. local regs = {...}
  523. if jit.arch == "x64" then
  524. for i=1,ngpr do
  525. out:write(format(" %016x", regs[i]))
  526. if i % 4 == 0 then out:write("\n") end
  527. end
  528. else
  529. for i=1,ngpr do
  530. out:write(format(" %08x", regs[i]))
  531. if i % 8 == 0 then out:write("\n") end
  532. end
  533. end
  534. for i=1,nfpr do
  535. out:write(format(" %+17.14g", regs[ngpr+i]))
  536. if i % 4 == 0 then out:write("\n") end
  537. end
  538. end
  539. end
  540. ------------------------------------------------------------------------------
  541. -- Detach dump handlers.
  542. local function dumpoff()
  543. if active then
  544. active = false
  545. jit.attach(dump_texit)
  546. jit.attach(dump_record)
  547. jit.attach(dump_trace)
  548. if out and out ~= stdout and out ~= stderr then out:close() end
  549. out = nil
  550. end
  551. end
  552. -- Open the output file and attach dump handlers.
  553. local function dumpon(opt, outfile)
  554. if active then dumpoff() end
  555. local colormode = os.getenv("COLORTERM") and "A" or "T"
  556. if opt then
  557. opt = gsub(opt, "[TAH]", function(mode) colormode = mode; return ""; end)
  558. end
  559. local m = { t=true, b=true, i=true, m=true, }
  560. if opt and opt ~= "" then
  561. local o = sub(opt, 1, 1)
  562. if o ~= "+" and o ~= "-" then m = {} end
  563. for i=1,#opt do m[sub(opt, i, i)] = (o ~= "-") end
  564. end
  565. dumpmode = m
  566. if m.t or m.b or m.i or m.s or m.m then
  567. jit.attach(dump_trace, "trace")
  568. end
  569. if m.b then
  570. jit.attach(dump_record, "record")
  571. if not bcline then bcline = require("jit.bc").line end
  572. end
  573. if m.x or m.X then
  574. jit.attach(dump_texit, "texit")
  575. end
  576. if not outfile then outfile = os.getenv("LUAJIT_DUMPFILE") end
  577. if outfile then
  578. out = outfile == "-" and stdout or assert(io.open(outfile, "w"))
  579. else
  580. out = stdout
  581. end
  582. m[colormode] = true
  583. if colormode == "A" then
  584. colorize = colorize_ansi
  585. irtype = irtype_ansi
  586. elseif colormode == "H" then
  587. colorize = colorize_html
  588. irtype = irtype_html
  589. out:write(header_html)
  590. else
  591. colorize = colorize_text
  592. irtype = irtype_text
  593. end
  594. active = true
  595. end
  596. -- Public module functions.
  597. module(...)
  598. on = dumpon
  599. off = dumpoff
  600. start = dumpon -- For -j command line option.