Compatible Android

This commit is contained in:
Andros Fenollosa
2016-11-03 00:05:36 +01:00
parent 7cb6af1390
commit 8ec8327e5e
1793 changed files with 440698 additions and 7 deletions

View File

@ -0,0 +1,915 @@
-- luainspect.ast - Lua Abstract Syntax Tree (AST) and token list operations.
--
-- Two main structures are maintained. A Metalua-style AST represents the
-- nested syntactic structure obtained from the parse.
-- A separate linear ordered list of tokens represents the syntactic structure
-- from the lexing, including line information (character positions only not row/columns),
-- comments, and keywords, which is originally built from the lineinfo attributes
-- injected by Metalua into the AST (IMPROVE: it probably would be simpler
-- to obtain this from the lexer directly rather then inferring it from the parsing).
-- During AST manipulations, the lineinfo maintained in the AST is ignored
-- because it was found more difficult to maintain and not in the optimal format.
--
-- The contained code deals with
-- - Building the AST from source.
-- - Building the tokenlist from the AST lineinfo.
-- - Querying the AST+tokenlist.
-- - Modifying the AST+tokenlist (including incremental parsing source -> AST)
-- - Annotating the AST with navigational info (e.g. parent links) to assist queries.
-- - Dumping the tokenlist for debugging.
--
-- (c) 2010 David Manura, MIT License.
--! require 'luainspect.typecheck' (context)
local mlc = require 'metalua.compiler'.new()
local M = {}
--[=TESTSUITE
-- utilities
local ops = {}
ops['=='] = function(a,b) return a == b end
local function check(opname, a, b)
local op = assert(ops[opname])
if not op(a,b) then
error("fail == " .. tostring(a) .. " " .. tostring(b))
end
end
--]=]
-- CATEGORY: debug
local function DEBUG(...)
if LUAINSPECT_DEBUG then
print('DEBUG:', ...)
end
end
-- Converts character position to row,column position in string src.
-- Add values are 1-indexed.
function M.pos_to_linecol(pos, src)
local linenum = 1
local lasteolpos = 0
for eolpos in src:gmatch"()\n" do
if eolpos > pos then break end
linenum = linenum + 1
lasteolpos = eolpos
end
local colnum = pos - lasteolpos
return linenum, colnum
end
-- Removes any sheband ("#!") line from Lua source string.
-- CATEGORY: Lua parsing
function M.remove_shebang(src)
local shebang = src:match("^#![^\r\n]*")
return shebang and (" "):rep(#shebang) .. src:sub(#shebang+1) or src
end
-- Custom version of loadstring that parses out line number info
-- CATEGORY: Lua parsing
function M.loadstring(src)
local f, err = loadstring(src, "")
if f then
return f
else
err = err:gsub('^%[string ""%]:', "")
local linenum = assert(err:match("(%d+):"))
local colnum = 0
local linenum2 = err:match("^%d+: '[^']+' expected %(to close '[^']+' at line (%d+)")
return nil, err, linenum, colnum, linenum2
end
end
-- helper for ast_from_string. Raises on error.
-- FIX? filename currently ignored in Metalua
-- CATEGORY: Lua parsing
local function ast_from_string_helper(src, filename)
return mlc:src_to_ast(src, filename)
end
-- Counts number of lines in text.
-- Warning: the decision of whether to count a trailing new-line in a file
-- or an empty file as a line is a little subjective. This function currently
-- defines the line count as 1 plus the number of new line characters.
-- CATEGORY: utility/string
local function linecount(text)
local n = 1
for _ in text:gmatch'\n' do
n = n + 1
end
return n
end
-- Converts Lua source string to Lua AST (via mlp/gg).
-- CATEGORY: Lua parsing
function M.ast_from_string(src, filename)
local ok, ast = pcall(ast_from_string_helper, src, filename)
if not ok then
local err = ast
err = err:match('[^\n]*')
err = err:gsub("^.-:%s*line", "line")
-- mlp.chunk prepending this is undesirable. error(msg,0) would be better in gg.lua. Reported.
-- TODO-Metalua: remove when fixed in Metalua.
local linenum, colnum = err:match("line (%d+), char (%d+)")
if not linenum then
-- Metalua libraries may return "...gg.lua:56: .../mlp_misc.lua:179: End-of-file expected"
-- without the normal line/char numbers given things like "if x then end end". Should be
-- fixed probably with gg.parse_error in _chunk in mlp_misc.lua.
-- TODO-Metalua: remove when fixed in Metalua.
linenum = linecount(src)
colnum = 1
end
local linenum2 = nil
return nil, err, linenum, colnum, linenum2
else
return ast
end
end
-- Simple comment parser. Returns Metalua-style comment.
-- CATEGORY: Lua lexing
local function quick_parse_comment(src)
local s = src:match"^%-%-([^\n]*)()\n$"
if s then return {s, 1, #src, 'short'} end
local _, s = src:match(lexer.lexer.patterns.long_comment .. '\r?\n?$')
if s then return {s, 1, #src, 'long'} end
return nil
end
--FIX:check new-line correctness
--note: currently requiring \n at end of single line comment to avoid
-- incremental compilation with `--x\nf()` and removing \n from still
-- recognizing as comment `--x`.
-- currently allowing \r\n at end of long comment since Metalua includes
-- it in lineinfo of long comment (FIX:Metalua?)
-- Gets length of longest prefix string in both provided strings.
-- Returns max n such that text1:sub(1,n) == text2:sub(1,n) and n <= max(#text1,#text2)
-- CATEGORY: string utility
local function longest_prefix(text1, text2)
local nmin = 0
local nmax = math.min(#text1, #text2)
while nmax > nmin do
local nmid = math.ceil((nmin+nmax)/2)
if text1:sub(1,nmid) == text2:sub(1,nmid) then
nmin = nmid
else
nmax = nmid-1
end
end
return nmin
end
-- Gets length of longest postfix string in both provided strings.
-- Returns max n such that text1:sub(-n) == text2:sub(-n) and n <= max(#text1,#text2)
-- CATEGORY: string utility
local function longest_postfix(text1, text2)
local nmin = 0
local nmax = math.min(#text1, #text2)
while nmax > nmin do
local nmid = math.ceil((nmin+nmax)/2)
if text1:sub(-nmid) == text2:sub(-nmid) then --[*]
nmin = nmid
else
nmax = nmid-1
end
end
return nmin
end -- differs from longest_prefix only on line [*]
-- Determines AST node that must be re-evaluated upon changing code string from
-- `src` to `bsrc`, given previous top_ast/tokenlist/src.
-- Note: decorates top_ast as side-effect.
-- If preserve is true, then does not expand AST match even if replacement is invalid.
-- CATEGORY: AST/tokenlist manipulation
function M.invalidated_code(top_ast, tokenlist, src, bsrc, preserve)
-- Converts posiiton range in src to position range in bsrc.
local function range_transform(src_fpos, src_lpos)
local src_nlpos = #src - src_lpos
local bsrc_fpos = src_fpos
local bsrc_lpos = #bsrc - src_nlpos
return bsrc_fpos, bsrc_lpos
end
if src == bsrc then return end -- up-to-date
-- Find range of positions in src that differences correspond to.
-- Note: for zero byte range, src_pos2 = src_pos1 - 1.
local npre = longest_prefix(src, bsrc)
local npost = math.min(#src-npre, longest_postfix(src, bsrc))
-- note: min avoids overlap ambiguity
local src_fpos, src_lpos = 1 + npre, #src - npost
-- Find smallest AST node containing src range above. May also
-- be contained in (smaller) comment or whitespace.
local match_ast, match_comment, iswhitespace =
M.smallest_ast_containing_range(top_ast, tokenlist, src_fpos, src_lpos)
DEBUG('invalidate-smallest:', match_ast and (match_ast.tag or 'notag'), match_comment, iswhitespace)
-- Determine which (ast, comment, or whitespace) to match, and get its pos range in src and bsrc.
local srcm_fpos, srcm_lpos, bsrcm_fpos, bsrcm_lpos, mast, mtype
if iswhitespace then
mast, mtype = nil, 'whitespace'
srcm_fpos, srcm_lpos = src_fpos, src_lpos
elseif match_comment then
mast, mtype = match_comment, 'comment'
srcm_fpos, srcm_lpos = match_comment.fpos, match_comment.lpos
else
mast, mtype = match_ast, 'ast'
repeat
srcm_fpos, srcm_lpos = M.ast_pos_range(mast, tokenlist)
if not srcm_fpos then
if mast == top_ast then
srcm_fpos, srcm_lpos = 1, #src
break
else
M.ensure_parents_marked(top_ast)
mast = mast.parent
end
end
until srcm_fpos
end
bsrcm_fpos, bsrcm_lpos = range_transform(srcm_fpos, srcm_lpos)
-- Never expand match if preserve specified.
if preserve then
return srcm_fpos, srcm_lpos, bsrcm_fpos, bsrcm_lpos, mast, mtype
end
-- Determine if replacement could break parent nodes.
local isreplacesafe
if mtype == 'whitespace' then
if bsrc:sub(bsrcm_fpos, bsrcm_lpos):match'^%s*$' then -- replaced with whitespace
if bsrc:sub(bsrcm_fpos-1, bsrcm_lpos+1):match'%s' then -- not eliminating whitespace
isreplacesafe = true
end
end
elseif mtype == 'comment' then
local m2src = bsrc:sub(bsrcm_fpos, bsrcm_lpos)
DEBUG('invalidate-comment[' .. m2src .. ']')
if quick_parse_comment(m2src) then -- replaced with comment
isreplacesafe = true
end
end
if isreplacesafe then -- return on safe replacement
return srcm_fpos, srcm_lpos, bsrcm_fpos, bsrcm_lpos, mast, mtype
end
-- Find smallest containing statement block that will compile (or top_ast).
while 1 do
match_ast = M.get_containing_statementblock(match_ast, top_ast)
if match_ast == top_ast then
return 1,#src, 1, #bsrc, match_ast, 'statblock'
-- entire AST invalidated
end
local srcm_fpos, srcm_lpos = M.ast_pos_range(match_ast, tokenlist)
local bsrcm_fpos, bsrcm_lpos = range_transform(srcm_fpos, srcm_lpos)
local msrc = bsrc:sub(bsrcm_fpos, bsrcm_lpos)
DEBUG('invalidate-statblock:', match_ast and match_ast.tag, '[' .. msrc .. ']')
if loadstring(msrc) then -- compiled
return srcm_fpos, srcm_lpos, bsrcm_fpos, bsrcm_lpos, match_ast, 'statblock'
end
M.ensure_parents_marked(top_ast)
match_ast = match_ast.parent
end
end
-- Walks AST `ast` in arbitrary order, visiting each node `n`, executing `fdown(n)` (if specified)
-- when doing down and `fup(n)` (if specified) when going if.
-- CATEGORY: AST walk
function M.walk(ast, fdown, fup)
assert(type(ast) == 'table')
if fdown then fdown(ast) end
for _,bast in ipairs(ast) do
if type(bast) == 'table' then
M.walk(bast, fdown, fup)
end
end
if fup then fup(ast) end
end
-- Replaces contents of table t1 with contents of table t2.
-- Does not change metatable (if any).
-- This function is useful for swapping one AST node with another
-- while preserving any references to the node.
-- CATEGORY: table utility
function M.switchtable(t1, t2)
for k in pairs(t1) do t1[k] = nil end
for k in pairs(t2) do t1[k] = t2[k] end
end
-- Inserts all elements in list bt at index i in list t.
-- CATEGORY: table utility
local function tinsertlist(t, i, bt)
local oldtlen, delta = #t, i - 1
for ti = #t + 1, #t + #bt do t[ti] = false end -- preallocate (avoid holes)
for ti = oldtlen, i, -1 do t[ti + #bt] = t[ti] end -- shift
for bi = 1, #bt do t[bi + delta] = bt[bi] end -- fill
end
--[=[TESTSUITE:
local function _tinsertlist(t, i, bt)
for bi=#bt,1,-1 do table.insert(t, i, bt[bi]) end
end -- equivalent but MUCH less efficient for large tables
local function _tinsertlist(t, i, bt)
for bi=1,#bt do table.insert(t, i+bi-1, bt[bi]) end
end -- equivalent but MUCH less efficient for large tables
local t = {}; tinsertlist(t, 1, {}); assert(table.concat(t)=='')
local t = {}; tinsertlist(t, 1, {2,3}); assert(table.concat(t)=='23')
local t = {4}; tinsertlist(t, 1, {2,3}); assert(table.concat(t)=='234')
local t = {2}; tinsertlist(t, 2, {3,4}); assert(table.concat(t)=='234')
local t = {4,5}; tinsertlist(t, 1, {2,3}); assert(table.concat(t)=='2345')
local t = {2,5}; tinsertlist(t, 2, {3,4}); assert(table.concat(t)=='2345')
local t = {2,3}; tinsertlist(t, 3, {4,5}); assert(table.concat(t)=='2345')
print 'DONE'
--]=]
-- Gets list of keyword positions related to node ast in source src
-- note: ast must be visible, i.e. have lineinfo (e.g. unlike `Id "self" definition).
-- Note: includes operators.
-- Note: Assumes ast Metalua-style lineinfo is valid.
-- CATEGORY: tokenlist build
function M.get_keywords(ast, src)
local list = {}
if not ast.lineinfo then return list end
-- examine space between each pair of children i and j.
-- special cases: 0 is before first child and #ast+1 is after last child
-- Put children in lexical order.
-- Some binary operations have arguments reversed from lexical order.
-- For example, `a > b` becomes `Op{'lt', `Id 'b', `Id 'a'}
local oast =
(ast.tag == 'Op' and #ast == 3 and tostring(ast[2].lineinfo.first):match('|L(%d+)') > tostring(ast[3].lineinfo.first):match('|L(%d+)'))
and {ast[1], ast[3], ast[2]} or ast
local i = 0
while i <= #ast do
-- j is node following i that has lineinfo
local j = i+1; while j < #ast+1 and not oast[j].lineinfo do j=j+1 end
-- Get position range [fpos,lpos] between subsequent children.
local fpos
if i == 0 then -- before first child
fpos = tonumber(tostring(ast.lineinfo.first):match('|L(%d+)'))
else
local last = oast[i].lineinfo.last; local c = last.comments
fpos = (c and #c > 0 and c[#c][3] or tostring(last):match('|L(%d+)')) + 1
end
local lpos
if j == #ast+1 then -- after last child
lpos = tonumber(tostring(ast.lineinfo.last):match('|L(%d+)'))
else
local first = oast[j].lineinfo.first; local c = first.comments
lpos = (c and #c > 0 and c[1][2] or tostring(first):match('|L(%d+)')) - 1
end
-- Find keyword in range.
local spos = fpos
repeat
local mfpos, tok, mlppos = src:match("^%s*()(%a+)()", spos)
if not mfpos then
mfpos, tok, mlppos = src:match("^%s*()(%p+)()", spos)
end
if mfpos then
local mlpos = mlppos-1
if mlpos > lpos then mlpos = lpos end
if mlpos >= mfpos then
list[#list+1] = mfpos
list[#list+1] = mlpos
end
end
spos = mlppos
until not spos or spos > lpos
-- note: finds single keyword. in `local function` returns only `local`
--DEBUG(i,j ,'test[' .. src:sub(fpos, lpos) .. ']')
i = j -- next
--DESIGN:Lua: comment: string.match accepts a start position but not a stop position
end
return list
end
-- Q:Metalua: does ast.lineinfo[loc].comments imply #ast.lineinfo[loc].comments > 0 ?
-- Generates ordered list of tokens in top_ast/src.
-- Note: currently ignores operators and parens.
-- Note: Modifies ast.
-- Note: Assumes ast Metalua-style lineinfo is valid.
-- CATEGORY: AST/tokenlist query
local isterminal = {Nil=true, Dots=true, True=true, False=true, Number=true, String=true,
Dots=true, Id=true}
local function compare_tokens_(atoken, btoken) return atoken.fpos < btoken.fpos end
function M.ast_to_tokenlist(top_ast, src)
local tokens = {} -- {nbytes=#src}
local isseen = {}
M.walk(top_ast, function(ast)
if isterminal[ast.tag] then -- Extract terminal
local token = ast
if ast.lineinfo then
token.fpos = tonumber(tostring(ast.lineinfo.first):match('|L(%d+)'))
token.lpos = tonumber(tostring(ast.lineinfo.last):match('|L(%d+)'))
token.ast = ast
table.insert(tokens, token)
end
else -- Extract non-terminal
local keywordposlist = M.get_keywords(ast, src)
for i=1,#keywordposlist,2 do
local fpos, lpos = keywordposlist[i], keywordposlist[i+1]
local toksrc = src:sub(fpos, lpos)
local token = {tag='Keyword', fpos=fpos, lpos=lpos, ast=ast, toksrc}
table.insert(tokens, token)
end
end
-- Extract comments
for i=1,2 do
local comments = ast.lineinfo and ast.lineinfo[i==1 and 'first' or 'last'].comments
if comments then for _, comment in ipairs(comments) do
if not isseen[comment] then
comment.tag = 'Comment'
local token = comment
token.fpos = tonumber(tostring(comment.lineinfo.first):match('|L(%d+)'))
token.lpos = tonumber(tostring(comment.lineinfo.last):match('|L(%d+)'))
token.ast = comment
table.insert(tokens, token)
isseen[comment] = true
end
end end
end
end, nil)
table.sort(tokens, compare_tokens_)
return tokens
end
-- Gets tokenlist range [fidx,lidx] covered by ast. Returns nil,nil if not found.
--FIX:PERFORMANCE:this is slow on large files.
-- CATEGORY: AST/tokenlist query
function M.ast_idx_range_in_tokenlist(tokenlist, ast)
-- Get list of primary nodes under ast.
local isold = {}; M.walk(ast, function(ast) isold[ast] = true end)
-- Get range.
local fidx, lidx
for idx=1,#tokenlist do
local token = tokenlist[idx]
if isold[token.ast] then
lidx = idx
if not fidx then fidx = idx end
end
end
return fidx, lidx
end
-- Gets index range in tokenlist overlapped by character position range [fpos, lpos].
-- For example, `do ff() end` with range ` ff() ` would match tokens `ff()`.
-- Tokens partly inside range are counted, so range `f()` would match tokens `ff()`.
-- If lidx = fidx - 1, then position range is whitespace between tokens lidx (on left)
-- and fidx (on right), and this may include token pseudoindices 0 (start of file) and
-- #tokenlist+1 (end of file).
-- Note: lpos == fpos - 1 indicates zero-width range between chars lpos and fpos.
-- CATEGORY: tokenlist query
function M.tokenlist_idx_range_over_pos_range(tokenlist, fpos, lpos)
-- Find first/last indices of tokens overlapped (even partly) by position range.
local fidx, lidx
for idx=1,#tokenlist do
local token = tokenlist[idx]
--if (token.fpos >= fpos and token.fpos <= lpos) or (token.lpos >= fpos and token.lpos <= lpos) then -- token overlaps range
if fpos <= token.lpos and lpos >= token.fpos then -- range overlaps token (even partially)
if not fidx then fidx = idx end
lidx = idx
end
end
if not fidx then -- on fail, check between tokens
for idx=1,#tokenlist+1 do -- between idx-1 and idx
local tokfpos, toklpos = tokenlist[idx-1] and tokenlist[idx-1].lpos, tokenlist[idx] and tokenlist[idx].fpos
if (not tokfpos or fpos > tokfpos) and (not toklpos or lpos < toklpos) then -- range between tokens
return idx, idx-1
end
end
end
return fidx, lidx
end
--[=[TESTSUITE
local function test(...)
return table.concat({M.tokenlist_idx_range_over_pos_range(...)}, ',')
end
check('==', test({}, 2, 2), "1,0") -- no tokens
check('==', test({{tag='Id', fpos=1, lpos=1}}, 2, 2), "2,1") -- right of one token
check('==', test({{tag='Id', fpos=3, lpos=3}}, 2, 2), "1,0") -- left of one token
check('==', test({{tag='Id', fpos=3, lpos=4}}, 2, 3), "1,1") -- left partial overlap one token
check('==', test({{tag='Id', fpos=3, lpos=4}}, 4, 5), "1,1") -- right partial overlap one token
check('==', test({{tag='Id', fpos=3, lpos=6}}, 4, 5), "1,1") -- partial inner overlap one token
check('==', test({{tag='Id', fpos=3, lpos=6}}, 3, 6), "1,1") -- exact overlap one token
check('==', test({{tag='Id', fpos=4, lpos=5}}, 3, 6), "1,1") -- extra overlap one token
check('==', test({{tag='Id', fpos=2, lpos=3}, {tag='Id', fpos=5, lpos=6}}, 4, 4), "2,1") -- between tokens, " " exact
check('==', test({{tag='Id', fpos=2, lpos=3}, {tag='Id', fpos=5, lpos=6}}, 4, 3), "2,1") -- between tokens, "" on left
check('==', test({{tag='Id', fpos=2, lpos=3}, {tag='Id', fpos=5, lpos=6}}, 5, 4), "2,1") -- between tokens, "" on right
check('==', test({{tag='Id', fpos=2, lpos=3}, {tag='Id', fpos=4, lpos=5}}, 4, 3), "2,1") -- between tokens, "" exact
--]=]
-- Removes tokens in tokenlist covered by ast.
-- CATEGORY: tokenlist manipulation
local function remove_ast_in_tokenlist(tokenlist, ast)
local fidx, lidx = M.ast_idx_range_in_tokenlist(tokenlist, ast)
if fidx then -- note: fidx implies lidx
for idx=lidx,fidx,-1 do table.remove(tokenlist, idx) end
end
end
-- Inserts tokens from btokenlist into tokenlist. Preserves sort.
-- CATEGORY: tokenlist manipulation
local function insert_tokenlist(tokenlist, btokenlist)
local ftoken = btokenlist[1]
if ftoken then
-- Get index in tokenlist in which to insert tokens in btokenlist.
local fidx
for idx=1,#tokenlist do
if tokenlist[idx].fpos > ftoken.fpos then fidx = idx; break end
end
fidx = fidx or #tokenlist + 1 -- else append
-- Insert tokens.
tinsertlist(tokenlist, fidx, btokenlist)
end
end
-- Get character position range covered by ast in tokenlist. Returns nil,nil on not found.
-- CATEGORY: AST/tokenlist query
function M.ast_pos_range(ast, tokenlist) -- IMPROVE:style: ast_idx_range_in_tokenlist has params reversed
local fidx, lidx = M.ast_idx_range_in_tokenlist(tokenlist, ast)
if fidx then
return tokenlist[fidx].fpos, tokenlist[lidx].lpos
else
return nil, nil
end
end
-- Gets string representation of AST node. nil if none.
-- IMPROVE: what if node is empty block?
-- CATEGORY: AST/tokenlist query
function M.ast_to_text(ast, tokenlist, src) -- IMPROVE:style: ast_idx_range_in_tokenlist has params reversed
local fpos, lpos = M.ast_pos_range(ast, tokenlist)
if fpos then
return src:sub(fpos, lpos)
else
return nil
end
end
-- Gets smallest AST node in top_ast/tokenlist/src
-- completely containing position range [pos1, pos2].
-- careful: "function" is not part of the `Function node.
-- If range is inside comment, returns comment also.
-- If range is inside whitespace, then returns true in third return value.
-- CATEGORY: AST/tokenlist query
function M.smallest_ast_containing_range(top_ast, tokenlist, pos1, pos2)
local f0idx, l0idx = M.tokenlist_idx_range_over_pos_range(tokenlist, pos1, pos2)
-- Find enclosing AST.
M.ensure_parents_marked(top_ast)
local fidx, lidx = f0idx, l0idx
while tokenlist[fidx] and not tokenlist[fidx].ast.parent do fidx = fidx - 1 end
while tokenlist[lidx] and not tokenlist[lidx].ast.parent do lidx = lidx + 1 end
-- DEBUG(fidx, lidx, f0idx, l0idx, #tokenlist, pos1, pos2, tokenlist[fidx], tokenlist[lidx])
local ast = not (tokenlist[fidx] and tokenlist[lidx]) and top_ast or
M.common_ast_parent(tokenlist[fidx].ast, tokenlist[lidx].ast, top_ast)
-- DEBUG('m2', tokenlist[fidx], tokenlist[lidx], top_ast, ast, ast and ast.tag)
if l0idx == f0idx - 1 then -- whitespace
return ast, nil, true
elseif l0idx == f0idx and tokenlist[l0idx].tag == 'Comment' then
return ast, tokenlist[l0idx], nil
else
return ast, nil, nil
end
end
--IMPROVE: handle string edits and maybe others
-- Gets smallest statement block containing position pos or
-- nearest statement block before pos, whichever is smaller, given ast/tokenlist.
function M.current_statementblock(ast, tokenlist, pos)
local fidx,lidx = M.tokenlist_idx_range_over_pos_range(tokenlist, pos, pos)
if fidx > lidx then fidx = lidx end -- use nearest backward
-- Find closest AST node backward
while fidx >= 1 and tokenlist[fidx].tag == 'Comment' do fidx=fidx-1 end
if fidx < 1 then return ast, false end
local mast = tokenlist[fidx].ast
if not mast then return ast, false end
mast = M.get_containing_statementblock(mast, ast)
local isafter = false
if mast.tag2 ~= 'Block' then
local mfidx,mlidx = M.ast_idx_range_in_tokenlist(tokenlist, mast)
if pos > mlidx then
isafter = true
end
end
return mast, isafter
end
-- Gets index of bast in ast (nil if not found).
-- CATEGORY: AST query
function M.ast_idx(ast, bast)
for idx=1,#ast do
if ast[idx] == bast then return idx end
end
return nil
end
-- Gets parent of ast and index of ast in parent.
-- Root node top_ast must also be provided. Returns nil, nil if ast is root.
-- Note: may call mark_parents.
-- CATEGORY: AST query
function M.ast_parent_idx(top_ast, ast)
if ast == top_ast then return nil, nil end
M.ensure_parents_marked(top_ast); assert(ast.parent)
local idx = M.ast_idx(ast.parent, ast)
return ast.parent, idx
end
-- Gets common parent of aast and bast. Always returns value.
-- Must provide root top_ast too.
-- CATEGORY: AST query
function M.common_ast_parent(aast, bast, top_ast)
M.ensure_parents_marked(top_ast)
local isparent = {}
local tast = bast; repeat isparent[tast] = true; tast = tast.parent until not tast
local uast = aast; repeat if isparent[uast] then return uast end; uast = uast.parent until not uast
assert(false)
end
-- Replaces old_ast with new_ast/new_tokenlist in top_ast/tokenlist.
-- Note: assumes new_ast is a block. assumes old_ast is a statement or block.
-- CATEGORY: AST/tokenlist
function M.replace_statements(top_ast, tokenlist, old_ast, new_ast, new_tokenlist)
remove_ast_in_tokenlist(tokenlist, old_ast)
insert_tokenlist(tokenlist, new_tokenlist)
if old_ast == top_ast then -- special case: no parent
M.switchtable(old_ast, new_ast) -- note: safe since block is not in tokenlist.
else
local parent_ast, idx = M.ast_parent_idx(top_ast, old_ast)
table.remove(parent_ast, idx)
tinsertlist(parent_ast, idx, new_ast)
end
-- fixup annotations
for _,bast in ipairs(new_ast) do
if top_ast.tag2 then M.mark_tag2(bast, bast.tag == 'Do' and 'StatBlock' or 'Block') end
if old_ast.parent then M.mark_parents(bast, old_ast.parent) end
end
end
-- Adjusts lineinfo in tokenlist.
-- All char positions starting at pos1 are shifted by delta number of chars.
-- CATEGORY: tokenlist
function M.adjust_lineinfo(tokenlist, pos1, delta)
for _,token in ipairs(tokenlist) do
if token.fpos >= pos1 then
token.fpos = token.fpos + delta
end
if token.lpos >= pos1 then
token.lpos = token.lpos + delta
end
end
--tokenlist.nbytes = tokenlist.nbytes + delta
end
-- For each node n in ast, sets n.parent to parent node of n.
-- Assumes ast.parent will be parent_ast (may be nil)
-- CATEGORY: AST query
function M.mark_parents(ast, parent_ast)
ast.parent = parent_ast
for _,ast2 in ipairs(ast) do
if type(ast2) == 'table' then
M.mark_parents(ast2, ast)
end
end
end
-- Calls mark_parents(ast) if ast not marked.
-- CATEGORY: AST query
function M.ensure_parents_marked(ast)
if ast[1] and not ast[1].parent then M.mark_parents(ast) end
end
-- For each node n in ast, sets n.tag2 to context string:
-- 'Block' - node is block
-- 'Stat' - node is statement
-- 'StatBlock' - node is statement and block (i.e. `Do)
-- 'Exp' - node is expression
-- 'Explist' - node is expression list (or identifier list)
-- 'Pair' - node is key-value pair in table constructor
-- note: ast.tag2 will be set to context.
-- CATEGORY: AST query
local iscertainstat = {Do=true, Set=true, While=true, Repeat=true, If=true,
Fornum=true, Forin=true, Local=true, Localrec=true, Return=true, Break=true}
function M.mark_tag2(ast, context)
context = context or 'Block'
ast.tag2 = context
for i,bast in ipairs(ast) do
if type(bast) == 'table' then
local nextcontext
if bast.tag == 'Do' then
nextcontext = 'StatBlock'
elseif iscertainstat[bast.tag] then
nextcontext = 'Stat'
elseif bast.tag == 'Call' or bast.tag == 'Invoke' then
nextcontext = context == 'Block' and 'Stat' or 'Exp'
--DESIGN:Metalua: these calls actually contain expression lists,
-- but the expression list is not represented as a complete node
-- by Metalua (as blocks are in `Do statements)
elseif bast.tag == 'Pair' then
nextcontext = 'Pair'
elseif not bast.tag then
if ast.tag == 'Set' or ast.tag == 'Local' or ast.tag == 'Localrec'
or ast.tag == 'Forin' and i <= 2
or ast.tag == 'Function' and i == 1
then
nextcontext = 'Explist'
else
nextcontext = 'Block'
end
else
nextcontext = 'Exp'
end
M.mark_tag2(bast, nextcontext)
end
end
end
-- Gets smallest statement or block containing or being `ast`.
-- The AST root node `top_ast` must also be provided.
-- Note: may decorate AST as side-effect (mark_tag2/mark_parents).
-- top_ast is assumed a block, so this is always successful.
-- CATEGORY: AST query
function M.get_containing_statementblock(ast, top_ast)
if not top_ast.tag2 then M.mark_tag2(top_ast) end
if ast.tag2 == 'Stat' or ast.tag2 == 'StatBlock' or ast.tag2 == 'Block' then
return ast
else
M.ensure_parents_marked(top_ast)
return M.get_containing_statementblock(ast.parent, top_ast)
end
end
-- Finds smallest statement, block, or comment AST in ast/tokenlist containing position
-- range [fpos, lpos]. If allowexpand is true (default nil) and located AST
-- coincides with position range, then next containing statement is used
-- instead (this allows multiple calls to further expand the statement selection).
-- CATEGORY: AST query
function M.select_statementblockcomment(ast, tokenlist, fpos, lpos, allowexpand)
--IMPROVE: rename ast to top_ast
local match_ast, comment_ast = M.smallest_ast_containing_range(ast, tokenlist, fpos, lpos)
local select_ast = comment_ast or M.get_containing_statementblock(match_ast, ast)
local nfpos, nlpos = M.ast_pos_range(select_ast, tokenlist)
--DEBUG('s', nfpos, nlpos, fpos, lpos, match_ast.tag, select_ast.tag)
if allowexpand and fpos == nfpos and lpos == nlpos then
if comment_ast then
-- Select enclosing statement.
select_ast = match_ast
nfpos, nlpos = M.ast_pos_range(select_ast, tokenlist)
else
-- note: multiple times may be needed to expand selection. For example, in
-- `for x=1,2 do f() end` both the statement `f()` and block `f()` have
-- the same position range.
M.ensure_parents_marked(ast)
while select_ast.parent and fpos == nfpos and lpos == nlpos do
select_ast = M.get_containing_statementblock(select_ast.parent, ast)
nfpos, nlpos = M.ast_pos_range(select_ast, tokenlist)
end
end
end
return nfpos, nlpos
end
-- Converts tokenlist to string representation for debugging.
-- CATEGORY: tokenlist debug
function M.dump_tokenlist(tokenlist)
local ts = {}
for i,token in ipairs(tokenlist) do
ts[#ts+1] = 'tok.' .. i .. ': [' .. token.fpos .. ',' .. token.lpos .. '] '
.. tostring(token[1]) .. ' ' .. tostring(token.ast.tag)
end
return table.concat(ts, '\n') -- .. 'nbytes=' .. tokenlist.nbytes .. '\n'
end
--FIX:Q: does this handle Unicode ok?
--FIX?:Metalua: fails on string with escape sequence '\/'. The Reference Manual
-- doesn't say this sequence is valid though.
--FIX:Metalua: In `local --[[x]] function --[[y]] f() end`,
-- 'x' comment omitted from AST.
--FIX:Metalua: `do --[[x]] end` doesn't generate comments in AST.
-- `if x then --[[x]] end` and `while 1 do --[[x]] end` generates
-- comments in first/last of block
--FIX:Metalua: `--[[x]] f() --[[y]]` returns lineinfo around `f()`.
-- `--[[x]] --[[y]]` returns lineinfo around everything.
--FIX:Metalua: `while 1 do --[[x]] --[[y]] end` returns first > last
-- lineinfo for contained block
--FIX:Metalua: search for "PATCHED:LuaInspect" in the metalualib folder.
--FIX?:Metalua: loadstring parses "--x" but metalua omits the comment in the AST
--FIX?:Metalua: `local x` is generating `Local{{`Id{x}}, {}}`, which
-- has no lineinfo on {}. This is contrary to the Metalua
-- spec: `Local{ {ident+} {expr+}? }.
-- Other things like `self` also generate no lineinfo.
-- The ast2.lineinfo above avoids this.
--FIX:Metalua: Metalua shouldn't overwrite ipairs/pairs. Note: Metalua version
-- doesn't set errorlevel correctly.
--Q:Metalua: Why does `return --[[y]] z --[[x]]` have
-- lineinfo.first.comments, lineinfo.last.comments,
-- plus lineinfo.comments (which is the same as lineinfo.first.comments) ?
--CAUTION:Metalua: `do f() end` returns lineinfo around `do f() end`, while
-- `while 1 do f() end` returns lineinfo around `f()` for inner block.
--CAUTION:Metalua: The lineinfo on Metalua comments is inconsistent with other
-- nodes
--CAUTION:Metalua: lineinfo of table in `f{}` is [3,2], of `f{ x,y }` it's [4,6].
-- This is inconsistent with `x={}` which is [3,4] and `f""` which is [1,2]
-- for the string.
--CAUTION:Metalua: only the `function()` form of `Function includes `function`
-- in lineinfo. 'function' is part of `Localrec and `Set in syntactic sugar form.
--[=[TESTSUITE
-- test longest_prefix/longest_postfix
local function pr(text1, text2)
local lastv
local function same(v)
assert(not lastv or v == lastv); lastv = v; return v
end
local function test1(text1, text2) -- test prefix/postfix
same(longest_prefix(text1, text2))
same(longest_postfix(text1:reverse(), text2:reverse()))
end
local function test2(text1, text2) -- test swap
test1(text1, text2)
test1(text2, text1)
end
for _,extra in ipairs{"", "x", "xy", "xyz"} do -- test extra chars
test2(text1, text2..extra)
test2(text2, text1..extra)
end
return lastv
end
check('==', pr("",""), 0)
check('==', pr("a",""), 0)
check('==', pr("a","a"), 1)
check('==', pr("ab",""), 0)
check('==', pr("ab","a"), 1)
check('==', pr("ab","ab"), 2)
check('==', pr("abcdefg","abcdefgh"), 7)
--]=]
--[=[TESTSUITE
print 'DONE'
--]=]
return M

View File

@ -0,0 +1,390 @@
--[[
compat_env v$(_VERSION) - Lua 5.1/5.2 environment compatibility functions
SYNOPSIS
-- Get load/loadfile compatibility functions only if using 5.1.
local CL = pcall(load, '') and _G or require 'compat_env'
local load = CL.load
local loadfile = CL.loadfile
-- The following now works in both Lua 5.1 and 5.2:
assert(load('return 2*pi', nil, 't', {pi=math.pi}))()
assert(loadfile('ex.lua', 't', {print=print}))()
-- Get getfenv/setfenv compatibility functions only if using 5.2.
local getfenv = _G.getfenv or require 'compat_env'.getfenv
local setfenv = _G.setfenv or require 'compat_env'.setfenv
local function f() return x end
setfenv(f, {x=2})
print(x, getfenv(f).x) --> 2, 2
DESCRIPTION
This module provides Lua 5.1/5.2 environment related compatibility functions.
This includes implementations of Lua 5.2 style `load` and `loadfile`
for use in Lua 5.1. It also includes Lua 5.1 style `getfenv` and `setfenv`
for use in Lua 5.2.
API
local CL = require 'compat_env'
CL.load (ld [, source [, mode [, env] ] ]) --> f [, err]
This behaves the same as the Lua 5.2 `load` in both
Lua 5.1 and 5.2.
http://www.lua.org/manual/5.2/manual.html#pdf-load
CL.loadfile ([filename [, mode [, env] ] ]) --> f [, err]
This behaves the same as the Lua 5.2 `loadfile` in both
Lua 5.1 and 5.2.
http://www.lua.org/manual/5.2/manual.html#pdf-loadfile
CL.getfenv ([f]) --> t
This is identical to the Lua 5.1 `getfenv` in Lua 5.1.
This behaves similar to the Lua 5.1 `getfenv` in Lua 5.2.
When a global environment is to be returned, or when `f` is a
C function, this returns `_G` since Lua 5.2 doesn't have
(thread) global and C function environments. This will also
return `_G` if the Lua function `f` lacks an `_ENV`
upvalue, but it will raise an error if uncertain due to lack of
debug info. It is not normally considered good design to use
this function; when possible, use `load` or `loadfile` instead.
http://www.lua.org/manual/5.1/manual.html#pdf-getfenv
CL.setfenv (f, t)
This is identical to the Lua 5.1 `setfenv` in Lua 5.1.
This behaves similar to the Lua 5.1 `setfenv` in Lua 5.2.
This will do nothing if `f` is a Lua function that
lacks an `_ENV` upvalue, but it will raise an error if uncertain
due to lack of debug info. See also Design Notes below.
It is not normally considered good design to use
this function; when possible, use `load` or `loadfile` instead.
http://www.lua.org/manual/5.1/manual.html#pdf-setfenv
DESIGN NOTES
This module intends to provide robust and fairly complete reimplementations
of the environment related Lua 5.1 and Lua 5.2 functions.
No effort is made, however, to simulate rare or difficult to simulate features,
such as thread environments, although this is liable to change in the future.
Such 5.1 capabilities are discouraged and ideally
removed from 5.1 code, thereby allowing your code to work in both 5.1 and 5.2.
In Lua 5.2, a `setfenv(f, {})`, where `f` lacks any upvalues, will be silently
ignored since there is no `_ENV` in this function to write to, and the
environment will have no effect inside the function anyway. However,
this does mean that `getfenv(setfenv(f, t))` does not necessarily equal `t`,
which is incompatible with 5.1 code (a possible workaround would be [1]).
If `setfenv(f, {})` has an upvalue but no debug info, then this will raise
an error to prevent inadvertently executing potentially untrusted code in the
global environment.
It is not normally considered good design to use `setfenv` and `getfenv`
(one reason they were removed in 5.2). When possible, consider replacing
these with `load` or `loadfile`, which are more restrictive and have native
implementations in 5.2.
This module might be merged into a more general Lua 5.1/5.2 compatibility
library (e.g. a full reimplementation of Lua 5.2 `_G`). However,
`load/loadfile/getfenv/setfenv` perhaps are among the more cumbersome
functions not to have.
INSTALLATION
Download compat_env.lua:
wget https://raw.github.com/gist/1654007/compat_env.lua
Copy compat_env.lua into your LUA_PATH.
Alternately, unpack, test, and install into LuaRocks:
wget https://raw.github.com/gist/1422205/sourceunpack.lua
lua sourceunpack.lua compat_env.lua
(cd out && luarocks make)
Related work
http://lua-users.org/wiki/LuaVersionCompatibility
https://github.com/stevedonovan/Penlight/blob/master/lua/pl/utils.lua
- penlight implementations of getfenv/setfenv
http://lua-users.org/lists/lua-l/2010-06/msg00313.html
- initial getfenv/setfenv implementation
References
[1] http://lua-users.org/lists/lua-l/2010-06/msg00315.html
Copyright
(c) 2012 David Manura. Licensed under the same terms as Lua 5.1/5.2 (MIT license).
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.
--]]---------------------------------------------------------------------
local M = {_TYPE='module', _NAME='compat_env', _VERSION='0.2.20120124'}
local function check_chunk_type(s, mode)
local nmode = mode or 'bt'
local is_binary = s and #s > 0 and s:byte(1) == 27
if is_binary and not nmode:match'b' then
return nil, ("attempt to load a binary chunk (mode is '%s')"):format(mode)
elseif not is_binary and not nmode:match't' then
return nil, ("attempt to load a text chunk (mode is '%s')"):format(mode)
end
return true
end
local IS_52_LOAD = pcall(load, '')
if IS_52_LOAD then
M.load = _G.load
M.loadfile = _G.loadfile
else
-- 5.2 style `load` implemented in 5.1
function M.load(ld, source, mode, env)
local f
if type(ld) == 'string' then
local s = ld
local ok, err = check_chunk_type(s, mode); if not ok then return ok, err end
local err; f, err = loadstring(s, source); if not f then return f, err end
elseif type(ld) == 'function' then
local ld2 = ld
if (mode or 'bt') ~= 'bt' then
local first = ld()
local ok, err = check_chunk_type(first, mode); if not ok then return ok, err end
ld2 = function()
if first then
local chunk=first; first=nil; return chunk
else return ld() end
end
end
local err; f, err = load(ld2, source); if not f then return f, err end
else
error(("bad argument #1 to 'load' (function expected, got %s)"):format(type(ld)), 2)
end
if env then setfenv(f, env) end
return f
end
-- 5.2 style `loadfile` implemented in 5.1
function M.loadfile(filename, mode, env)
if (mode or 'bt') ~= 'bt' then
local ioerr
local fh, err = io.open(filename, 'rb'); if not fh then return fh, err end
local function ld() local chunk; chunk,ioerr = fh:read(4096); return chunk end
local f, err = M.load(ld, filename and '@'..filename, mode, env)
fh:close()
if not f then return f, err end
if ioerr then return nil, ioerr end
return f
else
local f, err = loadfile(filename); if not f then return f, err end
if env then setfenv(f, env) end
return f
end
end
end
if _G.setfenv then -- Lua 5.1
M.setfenv = _G.setfenv
M.getfenv = _G.getfenv
else -- >= Lua 5.2
-- helper function for `getfenv`/`setfenv`
local function envlookup(f)
local name, val
local up = 0
local unknown
repeat
up=up+1; name, val = debug.getupvalue(f, up)
if name == '' then unknown = true end
until name == '_ENV' or name == nil
if name ~= '_ENV' then
up = nil
if unknown then error("upvalues not readable in Lua 5.2 when debug info missing", 3) end
end
return (name == '_ENV') and up, val, unknown
end
-- helper function for `getfenv`/`setfenv`
local function envhelper(f, name)
if type(f) == 'number' then
if f < 0 then
error(("bad argument #1 to '%s' (level must be non-negative)"):format(name), 3)
elseif f < 1 then
error("thread environments unsupported in Lua 5.2", 3) --[*]
end
f = debug.getinfo(f+2, 'f').func
elseif type(f) ~= 'function' then
error(("bad argument #1 to '%s' (number expected, got %s)"):format(type(name, f)), 2)
end
return f
end
-- [*] might simulate with table keyed by coroutine.running()
-- 5.1 style `setfenv` implemented in 5.2
function M.setfenv(f, t)
local f = envhelper(f, 'setfenv')
local up, val, unknown = envlookup(f)
if up then
debug.upvaluejoin(f, up, function() return up end, 1) -- unique upvalue [*]
debug.setupvalue(f, up, t)
else
local what = debug.getinfo(f, 'S').what
if what ~= 'Lua' and what ~= 'main' then -- not Lua func
error("'setfenv' cannot change environment of given object", 2)
end -- else ignore no _ENV upvalue (warning: incompatible with 5.1)
end
end
-- [*] http://lua-users.org/lists/lua-l/2010-06/msg00313.html
-- 5.1 style `getfenv` implemented in 5.2
function M.getfenv(f)
if f == 0 or f == nil then return _G end -- simulated behavior
local f = envhelper(f, 'setfenv')
local up, val = envlookup(f)
if not up then return _G end -- simulated behavior [**]
return val
end
-- [**] possible reasons: no _ENV upvalue, C function
end
return M
--[[ FILE rockspec.in
package = 'compat_env'
version = '$(_VERSION)-1'
source = {
url = 'https://raw.github.com/gist/1654007/$(GITID)/compat_env.lua',
--url = 'https://raw.github.com/gist/1654007/compat_env.lua', -- latest raw
--url = 'https://gist.github.com/gists/1654007/download',
md5 = '$(MD5)'
}
description = {
summary = 'Lua 5.1/5.2 environment compatibility functions',
detailed = [=[
Provides Lua 5.1/5.2 environment related compatibility functions.
This includes implementations of Lua 5.2 style `load` and `loadfile`
for use in Lua 5.1. It also includes Lua 5.1 style `getfenv` and `setfenv`
for use in Lua 5.2.
]=],
license = 'MIT/X11',
homepage = 'https://gist.github.com/1654007',
maintainer = 'David Manura'
}
dependencies = {} -- Lua 5.1 or 5.2
build = {
type = 'builtin',
modules = {
['compat_env'] = 'compat_env.lua'
}
}
--]]---------------------------------------------------------------------
--[[ FILE test.lua
-- test.lua - test suite for compat_env module.
local CL = require 'compat_env'
local load = CL.load
local loadfile = CL.loadfile
local setfenv = CL.setfenv
local getfenv = CL.getfenv
local function checkeq(a, b, e)
if a ~= b then error(
'not equal ['..tostring(a)..'] ['..tostring(b)..'] ['..tostring(e)..']')
end
end
local function checkerr(pat, ok, err)
assert(not ok, 'checkerr')
assert(type(err) == 'string' and err:match(pat), err)
end
-- test `load`
checkeq(load('return 2')(), 2)
checkerr('expected near', load'return 2 2')
checkerr('text chunk', load('return 2', nil, 'b'))
checkerr('text chunk', load('', nil, 'b'))
checkerr('binary chunk', load('\027', nil, 't'))
checkeq(load('return 2*x',nil,'bt',{x=5})(), 10)
checkeq(debug.getinfo(load('')).source, '')
checkeq(debug.getinfo(load('', 'foo')).source, 'foo')
-- test `loadfile`
local fh = assert(io.open('tmp.lua', 'wb'))
fh:write('return (...) or x')
fh:close()
checkeq(loadfile('tmp.lua')(2), 2)
checkeq(loadfile('tmp.lua', 't')(2), 2)
checkerr('text chunk', loadfile('tmp.lua', 'b'))
checkeq(loadfile('tmp.lua', nil, {x=3})(), 3)
checkeq(debug.getinfo(loadfile('tmp.lua')).source, '@tmp.lua')
checkeq(debug.getinfo(loadfile('tmp.lua', 't', {})).source, '@tmp.lua')
os.remove'tmp.lua'
-- test `setfenv`/`getfenv`
x = 5
local a,b=true; local function f(c) if a then return x,b,c end end
setfenv(f, {x=3})
checkeq(f(), 3)
checkeq(getfenv(f).x, 3)
checkerr('cannot change', pcall(setfenv, string.len, {})) -- C function
checkeq(getfenv(string.len), _G) -- C function
local function g()
setfenv(1, {x=4})
checkeq(getfenv(1).x, 4)
return x
end
checkeq(g(), 4) -- numeric level
if _G._VERSION ~= 'Lua 5.1' then
checkerr('unsupported', pcall(setfenv, 0, {}))
end
checkeq(getfenv(0), _G)
checkeq(getfenv(), _G) -- no arg
checkeq(x, 5) -- main unaltered
setfenv(function()end, {}) -- no upvalues, ignore
checkeq(getfenv(function()end), _G) -- no upvaluse
if _G._VERSION ~= 'Lua 5.1' then
checkeq(getfenv(setfenv(function()end, {})), _G) -- warning: incompatible with 5.1
end
x = nil
print 'OK'
--]]---------------------------------------------------------------------
--[[ FILE CHANGES.txt
0.2.20120124
Renamed module to compat_env (from compat_load)
Add getfenv/setfenv functions
0.1.20120121
Initial public release
--]]

View File

@ -0,0 +1,90 @@
-- Recursive object dumper, for debugging.
-- (c) 2010 David Manura, MIT License.
local M = {}
-- My own object dumper.
-- Intended for debugging, not serialization, with compact formatting.
-- Robust against recursion.
-- Renders Metalua table tag fields specially {tag=X, ...} --> "`X{...}".
-- On first call, only pass parameter o.
-- CATEGORY: AST debug
local ignore_keys_ = {lineinfo=true}
local norecurse_keys_ = {parent=true, ast=true}
local function dumpstring_key_(k, isseen, newindent)
local ks = type(k) == 'string' and k:match'^[%a_][%w_]*$' and k or
'[' .. M.dumpstring(k, isseen, newindent) .. ']'
return ks
end
local function sort_keys_(a, b)
if type(a) == 'number' and type(b) == 'number' then
return a < b
elseif type(a) == 'number' then
return false
elseif type(b) == 'number' then
return true
elseif type(a) == 'string' and type(b) == 'string' then
return a < b
else
return tostring(a) < tostring(b) -- arbitrary
end
end
function M.dumpstring(o, isseen, indent, key)
isseen = isseen or {}
indent = indent or ''
if type(o) == 'table' then
if isseen[o] or norecurse_keys_[key] then
return (type(o.tag) == 'string' and '`' .. o.tag .. ':' or '') .. tostring(o)
else isseen[o] = true end -- avoid recursion
local used = {}
local tag = o.tag
local s = '{'
if type(o.tag) == 'string' then
s = '`' .. tag .. s; used['tag'] = true
end
local newindent = indent .. ' '
local ks = {}; for k in pairs(o) do ks[#ks+1] = k end
table.sort(ks, sort_keys_)
--for i,k in ipairs(ks) do print ('keys', k) end
local forcenummultiline
for k in pairs(o) do
if type(k) == 'number' and type(o[k]) == 'table' then forcenummultiline = true end
end
-- inline elements
for _,k in ipairs(ks) do
if used[k] then -- skip
elseif ignore_keys_[k] then used[k] = true
elseif (type(k) ~= 'number' or not forcenummultiline) and
type(k) ~= 'table' and (type(o[k]) ~= 'table' or norecurse_keys_[k])
then
s = s .. dumpstring_key_(k, isseen, newindent) .. '=' .. M.dumpstring(o[k], isseen, newindent, k) .. ', '
used[k] = true
end
end
-- elements on separate lines
local done
for _,k in ipairs(ks) do
if not used[k] then
if not done then s = s .. '\n'; done = true end
s = s .. newindent .. dumpstring_key_(k, isseen) .. '=' .. M.dumpstring(o[k], isseen, newindent, k) .. ',\n'
end
end
s = s:gsub(',(%s*)$', '%1')
s = s .. (done and indent or '') .. '}'
return s
elseif type(o) == 'string' then
return string.format('%q', o)
else
return tostring(o)
end
end
return M

View File

@ -0,0 +1,222 @@
-- LuaInspect.globals - identifier scope analysis
-- Locates locals, globals, and their definitions.
--
-- (c) D.Manura, 2008-2010, MIT license.
-- based on http://lua-users.org/wiki/DetectingUndefinedVariables
local M = {}
--! require 'luainspect.typecheck' (context)
local LA = require "luainspect.ast"
local function definelocal(scope, name, ast)
if scope[name] then
scope[name].localmasked = true
ast.localmasking = scope[name]
end
scope[name] = ast
if name == '_' then ast.isignore = true end
end
-- Resolves scoping and usages of variable in AST.
-- Data Notes:
-- ast.localdefinition refers to lexically scoped definition of `Id node `ast`.
-- If ast.localdefinition == ast then ast is a "lexical definition".
-- If ast.localdefinition == nil, then variable is global.
-- ast.functionlevel is the number of functions the AST is contained in.
-- ast.functionlevel is defined iff ast is a lexical definition.
-- ast.isparam is true iff ast is a lexical definition and a function parameter.
-- ast.isset is true iff ast is a lexical definition and exists an assignment on it.
-- ast.isused is true iff ast is a lexical definition and has been referred to.
-- ast.isignore is true if local variable should be ignored (e.g. typically "_")
-- ast.localmasking - for a lexical definition, this is set to the lexical definition
-- this is masking (i.e. same name). nil if not masking.
-- ast.localmasked - true iff lexical definition masked by another lexical definition.
-- ast.isfield is true iff `String node ast is used for field access on object,
-- e.g. x.y or x['y'].z
-- ast.previous - For `Index{o,s} or `Invoke{o,s,...}, s.previous == o
local function traverse(ast, scope, globals, level, functionlevel)
scope = scope or {}
local blockrecurse
ast.level = level
-- operations on walking down the AST
if ast.tag == 'Local' then
blockrecurse = 1
-- note: apply new scope after processing values
elseif ast.tag == 'Localrec' then
local namelist_ast, valuelist_ast = ast[1], ast[2]
for _,value_ast in ipairs(namelist_ast) do
assert(value_ast.tag == 'Id')
local name = value_ast[1]
local parentscope = getmetatable(scope).__index
definelocal(parentscope, name, value_ast)
value_ast.localdefinition = value_ast
value_ast.functionlevel = functionlevel
value_ast.level = level+1
end
blockrecurse = 1
elseif ast.tag == 'Id' then
local name = ast[1]
if scope[name] then
ast.localdefinition = scope[name]
ast.functionlevel = functionlevel
scope[name].isused = true
else -- global, do nothing
end
elseif ast.tag == 'Function' then
local paramlist_ast, body_ast = ast[1], ast[2]
functionlevel = functionlevel + 1
for _,param_ast in ipairs(paramlist_ast) do
local name = param_ast[1]
assert(param_ast.tag == 'Id' or param_ast.tag == 'Dots')
if param_ast.tag == 'Id' then
definelocal(scope, name, param_ast)
param_ast.localdefinition = param_ast
param_ast.functionlevel = functionlevel
param_ast.isparam = true
end
param_ast.level = level+1
end
blockrecurse = 1
elseif ast.tag == 'Set' then
local reflist_ast, valuelist_ast = ast[1], ast[2]
for _,ref_ast in ipairs(reflist_ast) do
if ref_ast.tag == 'Id' then
local name = ref_ast[1]
if scope[name] then
scope[name].isset = true
else
if not globals[name] then
globals[name] = {set=ref_ast}
end
end
end
ref_ast.level = level+1
end
--ENHANCE? We could differentiate assignments to x (which indicates that
-- x is not const) and assignments to a member of x (which indicates that
-- x is not a pointer to const) and assignments to any nested member of x
-- (which indicates that x it not a transitive const).
elseif ast.tag == 'Fornum' then
blockrecurse = 1
elseif ast.tag == 'Forin' then
blockrecurse = 1
end
-- recurse (depth-first search down the AST)
if ast.tag == 'Repeat' then
local block_ast, cond_ast = ast[1], ast[2]
local scope = scope
for _,stat_ast in ipairs(block_ast) do
scope = setmetatable({}, {__index = scope})
traverse(stat_ast, scope, globals, level+1, functionlevel)
end
scope = setmetatable({}, {__index = scope})
traverse(cond_ast, scope, globals, level+1, functionlevel)
elseif ast.tag == 'Fornum' then
local name_ast, block_ast = ast[1], ast[#ast]
-- eval value list in current scope
for i=2, #ast-1 do traverse(ast[i], scope, globals, level+1, functionlevel) end
-- eval body in next scope
local name = name_ast[1]
definelocal(scope, name, name_ast)
name_ast.localdefinition = name_ast
name_ast.functionlevel = functionlevel
traverse(block_ast, scope, globals, level+1, functionlevel)
elseif ast.tag == 'Forin' then
local namelist_ast, vallist_ast, block_ast = ast[1], ast[2], ast[3]
-- eval value list in current scope
traverse(vallist_ast, scope, globals, level+1, functionlevel)
-- eval body in next scope
for _,name_ast in ipairs(namelist_ast) do
local name = name_ast[1]
definelocal(scope, name, name_ast)
name_ast.localdefinition = name_ast
name_ast.functionlevel = functionlevel
name_ast.level = level+1
end
traverse(block_ast, scope, globals, level+1, functionlevel)
else -- normal
for i,v in ipairs(ast) do
if i ~= blockrecurse and type(v) == 'table' then
local scope = setmetatable({}, {__index = scope})
traverse(v, scope, globals, level+1, functionlevel)
end
end
end
-- operations on walking up the AST
if ast.tag == 'Local' then
-- Unlike Localrec, variables come into scope after evaluating values.
local namelist_ast, valuelist_ast = ast[1], ast[2]
for _,name_ast in ipairs(namelist_ast) do
assert(name_ast.tag == 'Id')
local name = name_ast[1]
local parentscope = getmetatable(scope).__index
definelocal(parentscope, name, name_ast)
name_ast.localdefinition = name_ast
name_ast.functionlevel = functionlevel
name_ast.level = level+1
end
elseif ast.tag == 'Index' then
if ast[2].tag == 'String' then
ast[2].isfield = true
ast[2].previous = ast[1]
end
elseif ast.tag == 'Invoke' then
assert(ast[2].tag == 'String')
ast[2].isfield = true
ast[2].previous = ast[1]
end
end
function M.globals(ast)
-- Default list of defined variables.
local scope = setmetatable({}, {})
local globals = {}
traverse(ast, scope, globals, 1, 1) -- Start check.
return globals
end
-- Gets locals in scope of statement of block ast. If isafter is true and ast is statement,
-- uses scope just after statement ast.
-- Assumes 'parent' attributes on ast are marked.
-- Returns table mapping name -> AST local definition.
function M.variables_in_scope(ast, isafter)
local scope = {}
local cast = ast
while cast.parent do
local midx = LA.ast_idx(cast.parent, cast)
for idx=1,midx do
local bast = cast.parent[idx]
if bast.tag == 'Localrec' or bast.tag == 'Local' and (idx < midx or isafter) then
local names_ast = bast[1]
for bidx=1,#names_ast do
local name_ast = names_ast[bidx]
local name = name_ast[1]
scope[name] = name_ast
end
elseif cast ~= ast and (bast.tag == 'For' or bast.tag == 'Forin' or bast.tag == 'Function') then
local names_ast = bast[1]
for bidx=1,#names_ast do
local name_ast = names_ast[bidx]
if name_ast.tag == 'Id' then --Q: or maybe `Dots should be included
local name = name_ast[1]
scope[name] = name_ast
end
end
end
end
cast = cast.parent
end
return scope
end
return M

View File

@ -0,0 +1,433 @@
local M = {}
local T = require "luainspect.types"
-- signatures of known globals
M.global_signatures = {
assert = "assert (v [, message])",
collectgarbage = "collectgarbage (opt [, arg])",
dofile = "dofile (filename)",
error = "error (message [, level])",
_G = "(table)",
getfenv = "getfenv ([f])",
getmetatable = "getmetatable (object)",
ipairs = "ipairs (t)",
load = "load (func [, chunkname])",
loadfile = "loadfile ([filename])",
loadstring = "loadstring (string [, chunkname])",
next = "next (table [, index])",
pairs = "pairs (t)",
pcall = "pcall (f, arg1, ...)",
print = "print (...)",
rawequal = "rawequal (v1, v2)",
rawget = "rawget (table, index)",
rawset = "rawset (table, index, value)",
select = "select (index, ...)",
setfenv = "setfenv (f, table)",
setmetatable = "setmetatable (table, metatable)",
tonumber = "tonumber (e [, base])",
tostring = "tostring (e)",
type = "type (v)",
unpack = "unpack (list [, i [, j]])",
_VERSION = "(string)",
xpcall = "xpcall (f, err)",
module = "module (name [, ...])",
require = "require (modname)",
coroutine = "(table) coroutine manipulation library",
debug = "(table) debug facilities library",
io = "(table) I/O library",
math = "(table) math functions libary",
os = "(table) OS facilities library",
package = "(table) package library",
string = "(table) string manipulation library",
table = "(table) table manipulation library",
["coroutine.create"] = "coroutine.create (f)",
["coroutine.resume"] = "coroutine.resume (co [, val1, ...])",
["coroutine.running"] = "coroutine.running ()",
["coroutine.status"] = "coroutine.status (co)",
["coroutine.wrap"] = "coroutine.wrap (f)",
["coroutine.yield"] = "coroutine.yield (...)",
["debug.debug"] = "debug.debug ()",
["debug.getfenv"] = "debug.getfenv (o)",
["debug.gethook"] = "debug.gethook ([thread])",
["debug.getinfo"] = "debug.getinfo ([thread,] function [, what])",
["debug.getlocal"] = "debug.getlocal ([thread,] level, local)",
["debug.getmetatable"] = "debug.getmetatable (object)",
["debug.getregistry"] = "debug.getregistry ()",
["debug.getupvalue"] = "debug.getupvalue (func, up)",
["debug.setfenv"] = "debug.setfenv (object, table)",
["debug.sethook"] = "debug.sethook ([thread,] hook, mask [, count])",
["debug.setlocal"] = "debug.setlocal ([thread,] level, local, value)",
["debug.setmetatable"] = "debug.setmetatable (object, table)",
["debug.setupvalue"] = "debug.setupvalue (func, up, value)",
["debug.traceback"] = "debug.traceback ([thread,] [message] [, level])",
["io.close"] = "io.close ([file])",
["io.flush"] = "io.flush ()",
["io.input"] = "io.input ([file])",
["io.lines"] = "io.lines ([filename])",
["io.open"] = "io.open (filename [, mode])",
["io.output"] = "io.output ([file])",
["io.popen"] = "io.popen (prog [, mode])",
["io.read"] = "io.read (...)",
["io.tmpfile"] = "io.tmpfile ()",
["io.type"] = "io.type (obj)",
["io.write"] = "io.write (...)",
["math.abs"] = "math.abs (x)",
["math.acos"] = "math.acos (x)",
["math.asin"] = "math.asin (x)",
["math.atan"] = "math.atan (x)",
["math.atan2"] = "math.atan2 (y, x)",
["math.ceil"] = "math.ceil (x)",
["math.cos"] = "math.cos (x)",
["math.cosh"] = "math.cosh (x)",
["math.deg"] = "math.deg (x)",
["math.exp"] = "math.exp (x)",
["math.floor"] = "math.floor (x)",
["math.fmod"] = "math.fmod (x, y)",
["math.frexp"] = "math.frexp (x)",
["math.huge"] = "math.huge",
["math.ldexp"] = "math.ldexp (m, e)",
["math.log"] = "math.log (x)",
["math.log10"] = "math.log10 (x)",
["math.max"] = "math.max (x, ...)",
["math.min"] = "math.min (x, ...)",
["math.modf"] = "math.modf (x)",
["math.pi"] = "math.pi",
["math.pow"] = "math.pow (x, y)",
["math.rad"] = "math.rad (x)",
["math.random"] = "math.random ([m [, n]])",
["math.randomseed"] = "math.randomseed (x)",
["math.sin"] = "math.sin (x)",
["math.sinh"] = "math.sinh (x)",
["math.sqrt"] = "math.sqrt (x)",
["math.tan"] = "math.tan (x)",
["math.tanh"] = "math.tanh (x)",
["os.clock"] = "os.clock ()",
["os.date"] = "os.date ([format [, time]])",
["os.difftime"] = "os.difftime (t2, t1)",
["os.execute"] = "os.execute ([command])",
["os.exit"] = "os.exit ([code])",
["os.getenv"] = "os.getenv (varname)",
["os.remove"] = "os.remove (filename)",
["os.rename"] = "os.rename (oldname, newname)",
["os.setlocale"] = "os.setlocale (locale [, category])",
["os.time"] = "os.time ([table])",
["os.tmpname"] = "os.tmpname ()",
["package.cpath"] = "package.cpath",
["package.loaded"] = "package.loaded",
["package.loaders"] = "package.loaders",
["package.loadlib"] = "package.loadlib (libname, funcname)",
["package.path"] = "package.path",
["package.preload"] = "package.preload",
["package.seeall"] = "package.seeall (module)",
["string.byte"] = "string.byte (s [, i [, j]])",
["string.char"] = "string.char (...)",
["string.dump"] = "string.dump (function)",
["string.find"] = "string.find (s, pattern [, init [, plain]])",
["string.format"] = "string.format (formatstring, ...)",
["string.gmatch"] = "string.gmatch (s, pattern)",
["string.gsub"] = "string.gsub (s, pattern, repl [, n])",
["string.len"] = "string.len (s)",
["string.lower"] = "string.lower (s)",
["string.match"] = "string.match (s, pattern [, init])",
["string.rep"] = "string.rep (s, n)",
["string.reverse"] = "string.reverse (s)",
["string.sub"] = "string.sub (s, i [, j])",
["string.upper"] = "string.upper (s)",
["table.concat"] = "table.concat (table [, sep [, i [, j]]])",
["table.insert"] = "table.insert (table, [pos,] value)",
["table.maxn"] = "table.maxn (table)",
["table.remove"] = "table.remove (table [, pos])",
["table.sort"] = "table.sort (table [, comp])",
}
-- utility function. Converts e.g. name 'math.sqrt' to its value.
local function resolve_global_helper_(name)
local o = _G
for fieldname in name:gmatch'[^%.]+' do o = o[fieldname] end
return o
end
local function resolve_global(name)
local a, b = pcall(resolve_global_helper_, name)
if a then return b else return nil, b end
end
-- Same as global_signatures but maps value (not name) to signature.
M.value_signatures = {}
local isobject = {['function']=true, ['table']=true, ['userdata']=true, ['coroutine']=true}
for name,sig in pairs(M.global_signatures) do
local val, err = resolve_global(name)
if isobject[type(val)] then
M.value_signatures[val] = sig
end
end
-- min,max argument counts.
M.argument_counts = {
[assert] = {1,2},
[collectgarbage] = {1,2},
[dofile] = {1},
[error] = {1,2},
[getfenv or false] = {0,1},
[getmetatable] = {1,1},
[ipairs] = {1,1},
[load] = {1,2},
[loadfile] = {0,1},
[loadstring] = {1,2},
[next] = {1,2},
[pairs] = {1,1},
[pcall] = {1,math.huge},
[print] = {0,math.huge},
[rawequal] = {2,2},
[rawget] = {2,2},
[rawset] = {3,3},
[select] = {1, math.huge},
[setfenv or false] = {2,2},
[setmetatable] = {2,2},
[tonumber] = {1,2},
[tostring] = {1},
[type] = {1},
[unpack] = {1,3},
[xpcall] = {2,2},
[module] = {1,math.huge},
[require] = {1,1},
[coroutine.create] = {1,1},
[coroutine.resume] = {1, math.huge},
[coroutine.running] = {0,0},
[coroutine.status] = {1,1},
[coroutine.wrap] = {1,1},
[coroutine.yield] = {0,math.huge},
[debug.debug] = {0,0},
[debug.getfenv or false] = {1,1},
[debug.gethook] = {0,1},
[debug.getinfo] = {1,3},
[debug.getlocal] = {2,3},
[debug.getmetatable] = {1,1},
[debug.getregistry] = {0,0},
[debug.getupvalue] = {2,2},
[debug.setfenv or false] = {2,2},
[debug.sethook] = {2,4},
[debug.setlocal] = {3,4},
[debug.setmetatable] = {2,2},
[debug.setupvalue] = {3,3},
[debug.traceback] = {0,3},
[io.close] = {0,1},
[io.flush] = {0,0},
[io.input] = {0,1},
[io.lines] = {0,1},
[io.open] = {1,2},
[io.output] = {0,1},
[io.popen] = {1,2},
[io.read] = {0,math.huge},
[io.tmpfile] = {0},
[io.type] = {1},
[io.write] = {0,math.huge},
[math.abs] = {1},
[math.acos] = {1},
[math.asin] = {1},
[math.atan] = {1},
[math.atan2] = {2,2},
[math.ceil] = {1,1},
[math.cos] = {1,1},
[math.cosh] = {1,1},
[math.deg] = {1,1},
[math.exp] = {1,1},
[math.floor] = {1,1},
[math.fmod] = {2,2},
[math.frexp] = {1,1},
[math.ldexp] = {2,2},
[math.log] = {1,1},
[math.log10] = {1,1},
[math.max] = {1,math.huge},
[math.min] = {1,math.huge},
[math.modf] = {1,1},
[math.pow] = {2,2},
[math.rad] = {1,1},
[math.random] = {0,2},
[math.randomseed] = {1,1},
[math.sin] = {1,1},
[math.sinh] = {1,1},
[math.sqrt] = {1,1},
[math.tan] = {1,1},
[math.tanh] = {1,1},
[os.clock] = {0,0},
[os.date] = {0,2},
[os.difftime] = {2,2},
[os.execute] = {0,1},
[os.exit] = {0,1},
[os.getenv] = {1,1},
[os.remove] = {1,1},
[os.rename] = {2,2},
[os.setlocale] = {1,2},
[os.time] = {0,1},
[os.tmpname] = {0,0},
[package.loadlib] = {2,2},
[package.seeall] = {1,1},
[string.byte] = {1,3},
[string.char] = {0,math.huge},
[string.dump] = {1,1},
[string.find] = {2,4},
[string.format] = {1,math.huge},
[string.gmatch] = {2,2},
[string.gsub] = {3,4},
[string.len] = {1,1},
[string.lower] = {1,1},
[string.match] = {2,3},
[string.rep] = {2,2},
[string.reverse] = {1,1},
[string.sub] = {2,3},
[string.upper] = {1,1},
[table.concat] = {1,4},
[table.insert] = {2,3},
[table.maxn] = {1,1},
[table.remove] = {1,2},
[table.sort] = {1,2},
[false] = nil -- trick (relies on potentially undefined behavior)
}
-- functions with zero or nearly zero side-effects, and with deterministic results, that may be evaluated by the analyzer.
M.safe_function = {
[require] = true,
[rawequal] = true,
[rawget] = true,
[require] = true, -- sort of
[select] = true,
[tonumber] = true,
[tostring] = true,
[type] = true,
[unpack] = true,
[coroutine.create] = true,
-- [coroutine.resume]
[coroutine.running] = true,
[coroutine.status] = true,
[coroutine.wrap] = true,
--[coroutine.yield]
-- [debug.debug]
--[debug.getfenv] = true,
[debug.gethook] = true,
[debug.getinfo] = true,
[debug.getlocal] = true,
[debug.getmetatable] = true,
[debug.getregistry] = true,
[debug.getupvalue] = true,
-- [debug.setfenv]
-- [debug.sethook]
-- [debug.setlocal]
-- [debug.setmetatable]
-- [debug.setupvalue]
-- [debug.traceback] = true,
[io.type] = true,
-- skip all other io.*
[math.abs] = true,
[math.acos] = true,
[math.asin] = true,
[math.atan] = true,
[math.atan2] = true,
[math.ceil] = true,
[math.cos] = true,
[math.cosh] = true,
[math.deg] = true,
[math.exp] = true,
[math.floor] = true,
[math.fmod] = true,
[math.frexp] = true,
[math.ldexp] = true,
[math.log] = true,
[math.log10] = true,
[math.max] = true,
[math.min] = true,
[math.modf] = true,
[math.pow] = true,
[math.rad] = true,
--[math.random]
--[math.randomseed]
[math.sin] = true,
[math.sinh] = true,
[math.sqrt] = true,
[math.tan] = true,
[math.tanh] = true,
[os.clock] = true, -- safe but non-deterministic
[os.date] = true,-- safe but non-deterministic
[os.difftime] = true,
--[os.execute]
--[os.exit]
[os.getenv] = true, -- though depends on environment
--[os.remove]
--[os.rename]
--[os.setlocale]
[os.time] = true, -- safe but non-deterministic
--[os.tmpname]
[string.byte] = true,
[string.char] = true,
[string.dump] = true,
[string.find] = true,
[string.format] = true,
[string.gmatch] = true,
[string.gsub] = true,
[string.len] = true,
[string.lower] = true,
[string.match] = true,
[string.rep] = true,
[string.reverse] = true,
[string.sub] = true,
[string.upper] = true,
[table.maxn] = true,
}
M.mock_functions = {}
-- TODO:IMPROVE
local function mockfunction(func, ...)
local inputs = {n=0}
local outputs = {n=0}
local isoutputs
for i=1,select('#', ...) do
local v = select(i, ...)
if type(v) == 'table' then v = v[1] end
if v == 'N' or v == 'I' then v = T.number end
if v == '->' then
isoutputs = true
elseif isoutputs then
outputs[#outputs+1] = v; outputs.n = outputs.n + 1
else
inputs[#inputs+1] = v; inputs.n = inputs.n + 1
end
end
M.mock_functions[func] = {inputs=inputs, outputs=outputs}
end
mockfunction(math.abs, 'N', '->', {'N',0,math.huge})
mockfunction(math.acos, {'N',-1,1}, '->', {'N',0,math.pi/2})
mockfunction(math.asin, {'N',-1,1}, '->', {'N',-math.pi/2,math.pi/2})
mockfunction(math.atan, {'N',-math.huge,math.huge}, '->',
{'N',-math.pi/2,math.pi/2})
--FIX atan2
mockfunction(math.ceil, 'N','->','I')
mockfunction(math.cos, 'N','->',{'N',-1,1})
mockfunction(math.cosh, 'N','->',{'N',1,math.huge})
mockfunction(math.deg, 'N','->','N')
mockfunction(math.exp, 'N','->',{'N',0,math.huge})
mockfunction(math.floor, 'N','->','I')
mockfunction(math.fmod, 'N','N','->','N')
mockfunction(math.frexp, 'N','->',{'N',-1,1},'->','I')
mockfunction(math.ldexp, {'N','I'},'->','N')
mockfunction(math.log, {'N',0,math.huge},'->','N')
mockfunction(math.log10, {'N',0,math.huge},'->','N')
-- function max(...) print 'NOT IMPL'end
-- function min(...) print 'NOT IMPL'end
mockfunction(math.modf, 'N','->','I',{'N',-1,1})
mockfunction(math.pow, 'N','N','->','N') -- improve?
mockfunction(math.rad, 'N','->','N')
-- random = function() print 'NOT IMPL' end
mockfunction(math.randomseed, 'N')
mockfunction(math.sin, 'N','->',{'N',-1,1})
mockfunction(math.sinh, 'N','->','N')
mockfunction(math.sqrt, {'N',0,math.huge},'->',{'N',0,math.huge})
mockfunction(math.tan, 'N','->','N') -- improve?
mockfunction(math.tanh, 'N','->',{'N',-1,1})
return M

View File

@ -0,0 +1,40 @@
-- luainspect.typecheck - Type definitions used to check LuaInspect itself.
--
-- (c) 2010 David Manura, MIT License.
local T = require "luainspect.types"
local ast_mt = {__tostring = function(s) return 'AST' end}
return function(context)
-- AST type.
local ast = T.table {
tag = T.string,
lineinfo=T.table{first=T.table{comments=T.table{T.table{T.string,T.number,T.number}},T.number,T.number,T.number,T.string},
ast=T.table{comments=T.table{T.table{T.string,T.number,T.number}},T.number,T.number,T.number,T.string}},
isfield=T.boolean, tag2=T.string,
value=T.universal, valueself=T.number, valuelist=T.table{n=T.number, isvaluepegged=T.boolean},
resolvedname=T.string, definedglobal=T.boolean, id=T.number, isparam=T.boolean, isset=T.boolean, isused=T.boolean,
isignore=T.boolean,
functionlevel=T.number, localmasked=T.boolean, note=T.string, nocollect=T.table{}, isdead=T.boolean}
-- FIX: some of these are "boolean or nil" actually
ast.localdefinition=ast; ast.localmasking = ast
ast.previous = ast; ast.parent = ast
ast.seevalue = ast; ast.seenote=ast
setmetatable(ast, ast_mt)
ast[1] = ast; ast[2] = ast
context.apply_value('ast$', ast)
-- Token type.
context.apply_value('token$', T.table{
tag=T.string, fpos=T.number, lpos=T.number, keywordid=T.number, ast=ast, [1]=T.string
})
-- Lua source code string type.
context.apply_value('src$', '')
-- SciTE syler object type.
local nf = function()end
context.apply_value('^styler$', T.table{SetState=nf, More=nf, Current=nf, Forward=nf, StartStyling=nf, EndStyling=nf, language=T.string})
end

View File

@ -0,0 +1,130 @@
local T = {} -- types
-- istype[o] iff o represents a type (i.e. set of values)
T.istype = {}
-- iserror[o] iff o represents an error type (created via T.error).
T.iserror = {}
-- istabletype[o] iff o represents a table type (created by T.table).
T.istabletype = {}
-- Number type
T.number = {}
setmetatable(T.number, T.number)
function T.number.__tostring(self)
return 'number'
end
T.istype[T.number] = true
-- String type
T.string = {}
setmetatable(T.string, T.string)
function T.string.__tostring(self)
return 'string'
end
T.istype[T.string] = true
-- Boolean type
T.boolean = {}
setmetatable(T.boolean, T.boolean)
function T.boolean.__tostring(self)
return 'boolean'
end
T.istype[T.boolean] = true
-- Table type
function T.table(t)
T.istype[t] = true
T.istabletype[t] = true
return t
end
-- Universal type. This is a superset of all other types.
T.universal = {}
setmetatable(T.universal, T.universal)
function T.universal.__tostring(self)
return 'unknown'
end
T.istype[T.universal] = true
-- nil type. Represents `nil` but can be stored in tables.
T['nil'] = {}
setmetatable(T['nil'], T['nil'])
T['nil'].__tostring = function(self)
return 'nil'
end
T.istype[T['nil']] = true
-- None type. Represents a non-existent value, in a similar way
-- that `none` is used differently from `nil` in the Lua C API.
T.none = {}
setmetatable(T.none, T.none)
function T.none.__tostring(self)
return 'none'
end
T.istype[T.none] = true
-- Error type
local CError = {}; CError.__index = CError
function CError.__tostring(self) return "error:" .. tostring(self.value) end
function T.error(val)
local self = setmetatable({value=val}, CError)
T.istype[self] = true
T.iserror[self] = true
return self
end
-- Gets a type that is a superset of the two given types.
function T.superset_types(a, b)
if T.iserror[a] then return a end
if T.iserror[b] then return b end
if rawequal(a, b) then -- note: including nil == nil
return a
elseif type(a) == 'string' or a == T.string then
if type(b) == 'string' or b == T.string then
return T.string
else
return T.universal
end
elseif type(a) == 'number' or a == T.number then
if type(b) == 'number' or b == T.number then
return T.number
else
return T.universal
end
elseif type(a) == 'boolean' or a == T.boolean then
if type(b) == 'boolean' or b == T.boolean then
return T.boolean
else
return T.universal
end
else
return T.universal -- IMPROVE
end
end
--[[TESTS:
assert(T.superset_types(2, 2) == 2)
assert(T.superset_types(2, 3) == T.number)
assert(T.superset_types(2, T.number) == T.number)
assert(T.superset_types(T.number, T.string) == T.universal)
print 'DONE'
--]]
-- Determines whether type `o` certainly evaluates to true (true),
-- certainly evaluates to false (false) or could evaluate to either
-- true of false ('?').
function T.boolean_cast(o)
if T.iserror[o] then -- special case
return '?'
elseif o == nil or o == false or o == T['nil'] then -- all subsets of {nil, false}
return false
elseif o == T.universal or o == T.boolean then -- all supersets of boolean
return '?'
else -- all subsets of universal - {nil, false}
return true
end
end
return T