1--[[--
2 Additions to the core debug module.
3
4 The module table returned by `std.debug` also contains all of the entries
5 from the core debug table.  An hygienic way to import this module, then, is
6 simply to override the core `debug` locally:
7
8    local debug = require "std.debug"
9
10 The behaviour of the functions in this module are controlled by the value
11 of the global `_DEBUG`.  Not setting `_DEBUG` prior to requiring **any** of
12 stdlib's modules is equivalent to having `_DEBUG = true`.
13
14 The first line of Lua code in production quality projects that use stdlib
15 should be either:
16
17     _DEBUG = false
18
19 or alternatively, if you need to be careful not to damage the global
20 environment:
21
22     local init = require "std.debug_init"
23     init._DEBUG = false
24
25 This mitigates almost all of the overhead of argument typechecking in
26 stdlib API functions.
27
28 @module std.debug
29]]
30
31
32local debug_init = require "std.debug_init"
33local base       = require "std.base"
34
35local _DEBUG = debug_init._DEBUG
36local argerror, raise = base.argerror, base.raise
37local prototype, unpack = base.prototype, base.unpack
38local copy, split, tostring = base.copy, base.split, base.tostring
39local insert, last, len, maxn = base.insert, base.last, base.len, base.maxn
40local ipairs, pairs = base.ipairs, base.pairs
41
42
43local M
44
45
46-- Return a deprecation message if _DEBUG.deprecate is `nil`, otherwise "".
47local function DEPRECATIONMSG (version, name, extramsg, level)
48  if level == nil then level, extramsg = extramsg, nil end
49  extramsg = extramsg or "and will be removed entirely in a future release"
50
51  local _, where = pcall (function () error ("", level + 3) end)
52  if _DEBUG.deprecate == nil then
53    return (where .. string.format ("%s was deprecated in release %s, %s.\n",
54                                    name, tostring (version), extramsg))
55  end
56
57  return ""
58end
59
60
61-- Define deprecated functions when _DEBUG.deprecate is not "truthy",
62-- and write `DEPRECATIONMSG` output to stderr.
63local function DEPRECATED (version, name, extramsg, fn)
64  if fn == nil then fn, extramsg = extramsg, nil end
65
66  if not _DEBUG.deprecate then
67    return function (...)
68      io.stderr:write (DEPRECATIONMSG (version, name, extramsg, 2))
69      return fn (...)
70    end
71  end
72end
73
74
75local _setfenv = debug.setfenv
76
77local function setfenv (fn, env)
78  -- Unwrap functable:
79  if type (fn) == "table" then
80    fn = fn.call or (getmetatable (fn) or {}).__call
81  end
82
83  if _setfenv then
84    return _setfenv (fn, env)
85
86  else
87    -- From http://lua-users.org/lists/lua-l/2010-06/msg00313.html
88    local name
89    local up = 0
90    repeat
91      up = up + 1
92      name = debug.getupvalue (fn, up)
93    until name == '_ENV' or name == nil
94    if name then
95      debug.upvaluejoin (fn, up, function () return name end, 1)
96      debug.setupvalue (fn, up, env)
97    end
98
99    return fn
100  end
101end
102
103
104local _getfenv = rawget (_G, "getfenv")
105
106local getfenv = function (fn)
107  fn = fn or 1
108
109  -- Unwrap functable:
110  if type (fn) == "table" then
111    fn = fn.call or (getmetatable (fn) or {}).__call
112  end
113
114  if _getfenv then
115    if type (fn) == "number" then fn = fn + 1 end
116
117    -- Stack frame count is critical here, so ensure we don't optimise one
118    -- away in LuaJIT...
119    return _getfenv (fn), nil
120
121  else
122    if type (fn) == "number" then
123      fn = debug.getinfo (fn + 1, "f").func
124    end
125
126    local name, env
127    local up = 0
128    repeat
129      up = up + 1
130      name, env = debug.getupvalue (fn, up)
131    until name == '_ENV' or name == nil
132    return env
133  end
134end
135
136
137local function resulterror (name, i, extramsg, level)
138  level = level or 1
139  raise ("result", "from", name, i, extramsg, level + 1)
140end
141
142
143local function extramsg_toomany (bad, expected, actual)
144  local s = "no more than %d %s%s expected, got %d"
145  return s:format (expected, bad, expected == 1 and "" or "s", actual)
146end
147
148
149--- Strip trailing ellipsis from final argument if any, storing maximum
150-- number of values that can be matched directly in `t.maxvalues`.
151-- @tparam table t table to act on
152-- @string v element added to *t*, to match against ... suffix
153-- @treturn table *t* with ellipsis stripped and maxvalues field set
154local function markdots (t, v)
155  return (v:gsub ("%.%.%.$", function () t.dots = true return "" end))
156end
157
158
159--- Calculate permutations of type lists with and without [optionals].
160-- @tparam table t a list of expected types by argument position
161-- @treturn table set of possible type lists
162local function permute (t)
163  if t[#t] then t[#t] = t[#t]:gsub ("%]%.%.%.$", "...]") end
164
165  local p = {{}}
166  for i, v in ipairs (t) do
167    local optional = v:match "%[(.+)%]"
168
169    if optional == nil then
170      -- Append non-optional type-spec to each permutation.
171      for b = 1, #p do
172	insert (p[b], markdots (p[b], v))
173      end
174    else
175      -- Duplicate all existing permutations, and add optional type-spec
176      -- to the unduplicated permutations.
177      local o = #p
178      for b = 1, o do
179        p[b + o] = copy (p[b])
180        insert (p[b], markdots (p[b], optional))
181      end
182    end
183  end
184  return p
185end
186
187
188local function typesplit (types)
189  if type (types) == "string" then
190    types = split (types:gsub ("%s+or%s+", "|"), "%s*|%s*")
191  end
192  local r, seen, add_nil = {}, {}, false
193  for _, v in ipairs (types) do
194    local m = v:match "^%?(.+)$"
195    if m then
196      add_nil, v = true, m
197    end
198    if not seen[v] then
199      r[#r + 1] = v
200      seen[v] = true
201    end
202  end
203  if add_nil then
204    r[#r + 1] = "nil"
205  end
206  return r
207end
208
209
210local function projectuniq (fkey, tt)
211  -- project
212  local t = {}
213  for _, u in ipairs (tt) do
214    t[#t + 1] = u[fkey]
215  end
216
217  -- split and remove duplicates
218  local r, s = {}, {}
219  for _, e in ipairs (t) do
220    for _, v in ipairs (typesplit (e)) do
221      if s[v] == nil then
222	r[#r + 1], s[v] = v, true
223      end
224    end
225  end
226  return r
227end
228
229
230local function parsetypes (types)
231  local r, permutations = {}, permute (types)
232  for i = 1, #permutations[1] do
233    r[i] = projectuniq (i, permutations)
234  end
235  r.dots = permutations[1].dots
236  return r
237end
238
239
240--- Concatenate a table of strings using ", " and " or " delimiters.
241-- @tparam table alternatives a table of strings
242-- @treturn string string of elements from alternatives delimited by ", "
243--   and " or "
244local function concat (alternatives)
245  if len (alternatives) > 1 then
246    local t = copy (alternatives)
247    local top = table.remove (t)
248    t[#t] = t[#t] .. " or " .. top
249    alternatives = t
250  end
251  return table.concat (alternatives, ", ")
252end
253
254
255local function extramsg_mismatch (expectedtypes, actual, index)
256  local actualtype = prototype (actual)
257
258  -- Tidy up actual type for display.
259  if actualtype == "nil" then
260    actualtype = "no value"
261  elseif actualtype == "string" and actual:sub (1, 1) == ":" then
262    actualtype = actual
263  elseif type (actual) == "table" and next (actual) == nil then
264    local matchstr = "," .. table.concat (expectedtypes, ",") .. ","
265    if actualtype == "table" and matchstr == ",#list," then
266      actualtype = "empty list"
267    elseif actualtype == "table" or matchstr:match ",#" then
268      actualtype = "empty " .. actualtype
269    end
270  end
271
272  if index then
273    actualtype = actualtype .. " at index " .. tostring (index)
274  end
275
276  -- Tidy up expected types for display.
277  local expectedstr = expectedtypes
278  if type (expectedtypes) == "table" then
279    local t = {}
280    for i, v in ipairs (expectedtypes) do
281      if v == "func" then
282        t[i] = "function"
283      elseif v == "bool" then
284        t[i] = "boolean"
285      elseif v == "any" then
286        t[i] = "any value"
287      elseif v == "file" then
288        t[i] = "FILE*"
289      elseif not index then
290        t[i] = v:match "(%S+) of %S+" or v
291      else
292        t[i] = v
293      end
294    end
295    expectedstr = (concat (t) .. " expected"):
296                  gsub ("#table", "non-empty table"):
297                  gsub ("#list", "non-empty list"):
298                  gsub ("(%S+ of [^,%s]-)s? ", "%1s "):
299                  gsub ("(%S+ of [^,%s]-)s?,", "%1s,"):
300		  gsub ("(s, [^,%s]-)s? ", "%1s "):
301		  gsub ("(s, [^,%s]-)s?,", "%1s,"):
302		  gsub ("(of .-)s? or ([^,%s]-)s? ", "%1s or %2s ")
303  end
304
305  return expectedstr .. ", got " .. actualtype
306end
307
308
309local argcheck, argscheck  -- forward declarations
310
311if _DEBUG.argcheck then
312
313  --- Return index of the first mismatch between types and values, or `nil`.
314  -- @tparam table typelist a list of expected types
315  -- @tparam table valuelist a table of arguments to compare
316  -- @treturn int|nil position of first mismatch in *typelist*
317  local function match (typelist, valuelist)
318    local n = #typelist
319    for i = 1, n do  -- normal parameters
320      local ok = pcall (argcheck, "pcall", i, typelist[i], valuelist[i])
321      if not ok then return i end
322    end
323    for i = n + 1, maxn (valuelist) do -- additional values against final type
324      local ok = pcall (argcheck, "pcall", i, typelist[n], valuelist[i])
325      if not ok then return i end
326    end
327  end
328
329
330  --- Compare *check* against type of *actual*
331  -- @string check extended type name expected
332  -- @param actual object being typechecked
333  -- @treturn boolean `true` if *actual* is of type *check*, otherwise
334  --   `false`
335  local function checktype (check, actual)
336    if check == "any" and actual ~= nil then
337      return true
338    elseif check == "file" and io.type (actual) == "file" then
339      return true
340    end
341
342    local actualtype = type (actual)
343    if check == actualtype then
344      return true
345    elseif check == "bool" and actualtype == "boolean" then
346      return true
347    elseif check == "#table" then
348      if actualtype == "table" and next (actual) then
349        return true
350      end
351    elseif check == "function" or check == "func" then
352      if actualtype == "function" or
353          (getmetatable (actual) or {}).__call ~= nil
354      then
355         return true
356      end
357    elseif check == "int" then
358      if actualtype == "number" and actual == math.floor (actual) then
359        return true
360      end
361    elseif type (check) == "string" and check:sub (1, 1) == ":" then
362      if check == actual then
363        return true
364      end
365    end
366
367    actualtype = prototype (actual)
368    if check == actualtype then
369      return true
370    elseif check == "list" or check == "#list" then
371      if actualtype == "table" or actualtype == "List" then
372        local len, count = len (actual), 0
373        local i = next (actual)
374        repeat
375	  if i ~= nil then count = count + 1 end
376          i = next (actual, i)
377        until i == nil or count > len
378        if count == len and (check == "list" or count > 0) then
379          return true
380        end
381      end
382    elseif check == "object" then
383      if actualtype ~= "table" and type (actual) == "table" then
384        return true
385      end
386    end
387
388    return false
389  end
390
391
392  local function empty (t) return not next (t) end
393
394  -- Pattern to normalize: [types...] to [types]...
395  local last_pat = "^%[([^%]%.]+)%]?(%.*)%]?"
396
397  --- Diagnose mismatches between *valuelist* and type *permutations*.
398  -- @tparam table valuelist list of actual values to be checked
399  -- @tparam table argt table of precalculated values and handler functiens
400  local function diagnose (valuelist, argt)
401    local permutations = argt.permutations
402
403    local bestmismatch, t = 0
404    for i, typelist in ipairs (permutations) do
405      local mismatch = match (typelist, valuelist)
406      if mismatch == nil then
407        bestmismatch, t = nil, nil
408        break -- every *valuelist* matched types from this *typelist*
409      elseif mismatch > bestmismatch then
410        bestmismatch, t = mismatch, permutations[i]
411      end
412    end
413
414    if bestmismatch ~= nil then
415      -- Report an error for all possible types at bestmismatch index.
416      local i, expected = bestmismatch
417      if t.dots and i > #t then
418	expected = typesplit (t[#t])
419      else
420	expected = projectuniq (i, permutations)
421      end
422
423      -- This relies on the `permute()` algorithm leaving the longest
424      -- possible permutation (with dots if necessary) at permutations[1].
425      local typelist = permutations[1]
426
427      -- For "container of things", check all elements are a thing too.
428      if typelist[i] then
429	local check, contents = typelist[i]:match "^(%S+) of (%S-)s?$"
430	if contents and type (valuelist[i]) == "table" then
431	  for k, v in pairs (valuelist[i]) do
432	    if not checktype (contents, v) then
433	      argt.badtype (i, extramsg_mismatch (expected, v, k), 3)
434	    end
435	  end
436	end
437      end
438
439      -- Otherwise the argument type itself was mismatched.
440      if t.dots or #t >= maxn (valuelist) then
441        argt.badtype (i, extramsg_mismatch (expected, valuelist[i]), 3)
442      end
443    end
444
445    local n, t = maxn (valuelist), t or permutations[1]
446    if t and t.dots == nil and n > #t then
447      argt.badtype (#t + 1, extramsg_toomany (argt.bad, #t, n), 3)
448    end
449  end
450
451
452  function argcheck (name, i, expected, actual, level)
453    level = level or 2
454    expected = typesplit (expected)
455
456    -- Check actual has one of the types from expected
457    local ok = false
458    for _, expect in ipairs (expected) do
459      local check, contents = expect:match "^(%S+) of (%S-)s?$"
460      check = check or expect
461
462      -- Does the type of actual check out?
463      ok = checktype (check, actual)
464
465      -- For "table of things", check all elements are a thing too.
466      if ok and contents and type (actual) == "table" then
467        for k, v in pairs (actual) do
468          if not checktype (contents, v) then
469            argerror (name, i, extramsg_mismatch (expected, v, k), level + 1)
470          end
471        end
472      end
473      if ok then break end
474    end
475
476    if not ok then
477      argerror (name, i, extramsg_mismatch (expected, actual), level + 1)
478    end
479  end
480
481
482  -- Pattern to extract: fname ([types]?[, types]*)
483  local args_pat = "^%s*([%w_][%.%:%d%w_]*)%s*%(%s*(.*)%s*%)"
484
485  function argscheck (decl, inner)
486    -- Parse "fname (argtype, argtype, argtype...)".
487    local fname, argtypes = decl:match (args_pat)
488    if argtypes == "" then
489      argtypes = {}
490    elseif argtypes then
491      argtypes = split (argtypes, "%s*,%s*")
492    else
493      fname = decl:match "^%s*([%w_][%.%:%d%w_]*)"
494    end
495
496    -- Precalculate vtables once to make multiple calls faster.
497    local input, output = {
498      bad          = "argument",
499      badtype      = function (i, extramsg, level)
500		       level = level or 1
501		       argerror (fname, i, extramsg, level + 1)
502		     end,
503      permutations = permute (argtypes),
504    }
505
506    -- Parse "... => returntype, returntype, returntype...".
507    local returntypes = decl:match "=>%s*(.+)%s*$"
508    if returntypes then
509      local i, permutations = 0, {}
510      for _, group in ipairs (split (returntypes, "%s+or%s+")) do
511	returntypes = split (group, ",%s*")
512	for _, t in ipairs (permute (returntypes)) do
513	  i = i + 1
514          permutations[i] = t
515	end
516      end
517
518      -- Ensure the longest permutation is first in the list.
519      table.sort (permutations, function (a, b) return #a > #b end)
520
521      output = {
522        bad          = "result",
523        badtype      = function (i, extramsg, level)
524		         level = level or 1
525		         resulterror (fname, i, extramsg, level + 1)
526		       end,
527        permutations = permutations,
528      }
529    end
530
531    return function (...)
532      local argt = {...}
533
534      -- Don't check type of self if fname has a ':' in it.
535      if fname:find (":") then table.remove (argt, 1) end
536
537      -- Diagnose bad inputs.
538      diagnose (argt, input)
539
540      -- Propagate outer environment to inner function.
541      local x = math.max -- ??? getfenv(1) fails if we remove this ???
542      setfenv (inner, getfenv (1))
543
544      -- Execute.
545      local results = {inner (...)}
546
547      -- Diagnose bad outputs.
548      if returntypes then
549	diagnose (results, output)
550      end
551
552      return unpack (results, 1, maxn (results))
553    end
554  end
555
556else
557
558  -- Turn off argument checking if _DEBUG is false, or a table containing
559  -- a false valued `argcheck` field.
560
561  argcheck  = base.nop
562  argscheck = function (decl, inner) return inner end
563
564end
565
566
567local function say (n, ...)
568  local level, argt = n, {...}
569  if type (n) ~= "number" then
570    level, argt = 1, {n, ...}
571  end
572  if _DEBUG.level ~= math.huge and
573      ((type (_DEBUG.level) == "number" and _DEBUG.level >= level) or level <= 1)
574  then
575    local t = {}
576    for k, v in pairs (argt) do t[k] = tostring (v) end
577    io.stderr:write (table.concat (t, "\t") .. "\n")
578  end
579end
580
581
582local level = 0
583
584local function trace (event)
585  local t = debug.getinfo (3)
586  local s = " >>> "
587  for i = 1, level do s = s .. " " end
588  if t ~= nil and t.currentline >= 0 then
589    s = s .. t.short_src .. ":" .. t.currentline .. " "
590  end
591  t = debug.getinfo (2)
592  if event == "call" then
593    level = level + 1
594  else
595    level = math.max (level - 1, 0)
596  end
597  if t.what == "main" then
598    if event == "call" then
599      s = s .. "begin " .. t.short_src
600    else
601      s = s .. "end " .. t.short_src
602    end
603  elseif t.what == "Lua" then
604    s = s .. event .. " " .. (t.name or "(Lua)") .. " <" ..
605      t.linedefined .. ":" .. t.short_src .. ">"
606  else
607    s = s .. event .. " " .. (t.name or "(C)") .. " [" .. t.what .. "]"
608  end
609  io.stderr:write (s .. "\n")
610end
611
612-- Set hooks according to _DEBUG
613if type (_DEBUG) == "table" and _DEBUG.call then
614  debug.sethook (trace, "cr")
615end
616
617
618
619M = {
620  --- Provide a deprecated function definition according to _DEBUG.deprecate.
621  -- You can check whether your covered code uses deprecated functions by
622  -- setting `_DEBUG.deprecate` to  `true` before loading any stdlib modules,
623  -- or silence deprecation warnings by setting `_DEBUG.deprecate = false`.
624  -- @function DEPRECATED
625  -- @string version first deprecation release version
626  -- @string name function name for automatic warning message
627  -- @string[opt] extramsg additional warning text
628  -- @func fn deprecated function
629  -- @return a function to show the warning on first call, and hand off to *fn*
630  -- @usage
631  -- M.op = DEPRECATED ("41", "'std.functional.op'", std.operator)
632  DEPRECATED = DEPRECATED,
633
634  --- Format a deprecation warning message.
635  -- @function DEPRECATIONMSG
636  -- @string version first deprecation release version
637  -- @string name function name for automatic warning message
638  -- @string[opt] extramsg additional warning text
639  -- @int level call stack level to blame for the error
640  -- @treturn string deprecation warning message, or empty string
641  -- @usage
642  -- io.stderr:write (DEPRECATIONMSG ("42", "multi-argument 'module.fname'", 2))
643  DEPRECATIONMSG = DEPRECATIONMSG,
644
645  --- Check the type of an argument against expected types.
646  -- Equivalent to luaL_argcheck in the Lua C API.
647  --
648  -- Call `argerror` if there is a type mismatch.
649  --
650  -- Argument `actual` must match one of the types from in `expected`, each
651  -- of which can be the name of a primitive Lua type, a stdlib object type,
652  -- or one of the special options below:
653  --
654  --    #table    accept any non-empty table
655  --    any       accept any non-nil argument type
656  --    file      accept an open file object
657  --    function  accept a function, or object with a __call metamethod
658  --    int       accept an integer valued number
659  --    list      accept a table where all keys are a contiguous 1-based integer range
660  --    #list     accept any non-empty list
661  --    object    accept any std.Object derived type
662  --    :foo      accept only the exact string ":foo", works for any :-prefixed string
663  --
664  -- The `:foo` format allows for type-checking of self-documenting
665  -- boolean-like constant string parameters predicated on `nil` versus
666  -- `:option` instead of `false` versus `true`.  Or you could support
667  -- both:
668  --
669  --    argcheck ("table.copy", 2, "boolean|:nometa|nil", nometa)
670  --
671  -- A very common pattern is to have a list of possible types including
672  -- "nil" when the argument is optional.  Rather than writing long-hand
673  -- as above, prepend a question mark to the list of types and omit the
674  -- explicit "nil" entry:
675  --
676  --    argcheck ("table.copy", 2, "?boolean|:nometa", predicate)
677  --
678  -- Normally, you should not need to use the `level` parameter, as the
679  -- default is to blame the caller of the function using `argcheck` in
680  -- error messages; which is almost certainly what you want.
681  -- @function argcheck
682  -- @string name function to blame in error message
683  -- @int i argument number to blame in error message
684  -- @string expected specification for acceptable argument types
685  -- @param actual argument passed
686  -- @int[opt=2] level call stack level to blame for the error
687  -- @usage
688  -- local function case (with, branches)
689  --   argcheck ("std.functional.case", 2, "#table", branches)
690  --   ...
691  argcheck = argcheck,
692
693  --- Raise a bad argument error.
694  -- Equivalent to luaL_argerror in the Lua C API. This function does not
695  -- return.  The `level` argument behaves just like the core `error`
696  -- function.
697  -- @function argerror
698  -- @string name function to callout in error message
699  -- @int i argument number
700  -- @string[opt] extramsg additional text to append to message inside parentheses
701  -- @int[opt=1] level call stack level to blame for the error
702  -- @see resulterror
703  -- @see extramsg_mismatch
704  -- @usage
705  -- local function slurp (file)
706  --   local h, err = input_handle (file)
707  --   if h == nil then argerror ("std.io.slurp", 1, err, 2) end
708  --   ...
709  argerror = argerror,
710
711  --- Wrap a function definition with argument type and arity checking.
712  -- In addition to checking that each argument type matches the corresponding
713  -- element in the *types* table with `argcheck`, if the final element of
714  -- *types* ends with an ellipsis, remaining unchecked arguments are checked
715  -- against that type:
716  --
717  --     format = argscheck ("string.format (string, ?any...)", string.format)
718  --
719  -- A colon in the function name indicates that the argument type list does
720  -- not have a type for `self`:
721  --
722  --     format = argscheck ("string:format (?any...)", string.format)
723  --
724  -- If an argument can be omitted entirely, then put its type specification
725  -- in square brackets:
726  --
727  --     insert = argscheck ("table.insert (table, [int], ?any)", table.insert)
728  --
729  -- Similarly return types can be checked with the same list syntax as
730  -- arguments:
731  --
732  --     len = argscheck ("string.len (string) => int", string.len)
733  --
734  -- Additionally, variant return type lists can be listed like this:
735  --
736  --     open = argscheck ("io.open (string, ?string) => file or nil, string",
737  --                       io.open)
738  --
739  -- @function argscheck
740  -- @string decl function type declaration string
741  -- @func inner function to wrap with argument checking
742  -- @usage
743  -- local case = argscheck ("std.functional.case (?any, #table) => [any...]",
744  --   function (with, branches)
745  --     ...
746  -- end)
747  argscheck = argscheck,
748
749  --- Format a type mismatch error.
750  -- @function extramsg_mismatch
751  -- @string expected a pipe delimited list of matchable types
752  -- @param actual the actual argument to match with
753  -- @number[opt] index erroring container element index
754  -- @treturn string formatted *extramsg* for this mismatch for @{argerror}
755  -- @see argerror
756  -- @see resulterror
757  -- @usage
758  --   if fmt ~= nil and type (fmt) ~= "string" then
759  --     argerror ("format", 1, extramsg_mismatch ("?string", fmt))
760  --   end
761  extramsg_mismatch = function (expected, actual, index)
762    return extramsg_mismatch (typesplit (expected), actual, index)
763  end,
764
765  --- Format a too many things error.
766  -- @string bad the thing there are too many of
767  -- @int expected maximum number of *bad* things expected
768  -- @int actual actual number of *bad* things that triggered the error
769  -- @see argerror
770  -- @see resulterror
771  -- @see extramsg_mismatch
772  -- @usage
773  --   if maxn (argt) > 7 then
774  --     argerror ("sevenses", 8, extramsg_toomany ("argument", 7, maxn (argt)))
775  --   end
776  extramsg_toomany = extramsg_toomany,
777
778  --- Extend `debug.getfenv` to unwrap functables correctly.
779  -- @tparam int|function|functable fn target function, or stack level
780  -- @treturn table environment of *fn*
781  getfenv = getfenv,
782
783  --- Compact permutation list into a list of valid types at each argument.
784  -- Eliminate bracketed types by combining all valid types at each position
785  -- for all permutations of *typelist*.
786  -- @function parsetypes
787  -- @tparam list types a normalized list of type names
788  -- @treturn list valid types for each positional parameter
789  parsetypes = parsetypes,
790
791  --- Raise a bad result error.
792  -- Like @{argerror} for bad results. This function does not
793  -- return.  The `level` argument behaves just like the core `error`
794  -- function.
795  -- @string name function to callout in error message
796  -- @int i argument number
797  -- @string[opt] extramsg additional text to append to message inside parentheses
798  -- @int[opt=1] level call stack level to blame for the error
799  -- @usage
800  -- local function slurp (file)
801  --   local h, err = input_handle (file)
802  --   if h == nil then argerror ("std.io.slurp", 1, err, 2) end
803  --   ...
804  resulterror = resulterror,
805
806  --- Extend `debug.setfenv` to unwrap functables correctly.
807  -- @tparam function|functable fn target function
808  -- @tparam table env new function environment
809  -- @treturn function *fn*
810  setfenv = setfenv,
811
812  --- Print a debugging message to `io.stderr`.
813  -- Display arguments passed through `std.tostring` and separated by tab
814  -- characters when `_DEBUG` is `true` and *n* is 1 or less; or `_DEBUG.level`
815  -- is a number greater than or equal to *n*.  If `_DEBUG` is false or
816  -- nil, nothing is written.
817  -- @function say
818  -- @int[opt=1] n debugging level, smaller is higher priority
819  -- @param ... objects to print (as for print)
820  -- @usage
821  -- local _DEBUG = require "std.debug_init"._DEBUG
822  -- _DEBUG.level = 3
823  -- say (2, "_DEBUG table contents:", _DEBUG)
824  say = say,
825
826  --- Trace function calls.
827  -- Use as debug.sethook (trace, "cr"), which is done automatically
828  -- when `_DEBUG.call` is set.
829  -- Based on test/trace-calls.lua from the Lua distribution.
830  -- @function trace
831  -- @string event event causing the call
832  -- @usage
833  -- _DEBUG = { call = true }
834  -- local debug = require "std.debug"
835  trace = trace,
836
837  --- Split a typespec string into a table of normalized type names.
838  -- @tparam string|table either `"?bool|:nometa"` or `{"boolean", ":nometa"}`
839  -- @treturn table a new list with duplicates removed and leading "?"s
840  --   replaced by a "nil" element
841  typesplit = typesplit,
842
843
844  -- Private:
845  _setdebug = function (t)
846    for k, v in pairs (t) do
847      if v == "nil" then v = nil end
848      _DEBUG[k] = v
849    end
850  end,
851}
852
853
854for k, v in pairs (debug) do
855  M[k] = M[k] or v
856end
857
858--- Equivalent to calling `debug.say (1, ...)`
859-- @function debug
860-- @see say
861-- @usage
862-- local debug = require "std.debug"
863-- debug "oh noes!"
864local metatable = {
865  __call = function (self, ...)
866             M.say (1, ...)
867           end,
868}
869
870
871
872--[[ =========== ]]--
873--[[ Deprecated. ]]--
874--[[ =========== ]]--
875
876
877M.toomanyargmsg = DEPRECATED ("41.2.0", "debug.toomanyargmsg",
878  "use 'debug.extramsg_toomany' instead",
879  function (name, expect, actual)
880    local s = "bad argument #%d to '%s' (no more than %d argument%s expected, got %d)"
881    return s:format (expect + 1, name, expect, expect == 1 and "" or "s", actual)
882  end)
883
884
885return setmetatable (M, metatable)
886
887
888
889--- Control std.debug function behaviour.
890-- To declare debugging state, set _DEBUG either to `false` to disable all
891-- runtime debugging; to any "truthy" value (equivalent to enabling everything
892-- except *call*, or as documented below.
893-- @class table
894-- @name _DEBUG
895-- @tfield[opt=true] boolean argcheck honor argcheck and argscheck calls
896-- @tfield[opt=false] boolean call do call trace debugging
897-- @field[opt=nil] deprecate if `false`, deprecated APIs are defined,
898--   and do not issue deprecation warnings when used; if `nil` issue a
899--   deprecation warning each time a deprecated api is used; any other
900--   value causes deprecated APIs not to be defined at all
901-- @tfield[opt=1] int level debugging level
902-- @usage _DEBUG = { argcheck = false, level = 9 }
903