diff options
author | chai <chaifix@163.com> | 2021-11-17 23:03:07 +0800 |
---|---|---|
committer | chai <chaifix@163.com> | 2021-11-17 23:03:07 +0800 |
commit | 27d6efb5f5a076f825fe2da1875e0cabaf02b4e7 (patch) | |
tree | 44f301110bc2ea742908ed92a78eba0803cd3b60 /Tools | |
parent | b34310c631989551054d456eb47aaab5ded266a4 (diff) |
+ LuaMacro
Diffstat (limited to 'Tools')
69 files changed, 5821 insertions, 0 deletions
diff --git a/Tools/LuaMacro/config.ld b/Tools/LuaMacro/config.ld new file mode 100644 index 0000000..40e3744 --- /dev/null +++ b/Tools/LuaMacro/config.ld @@ -0,0 +1,8 @@ +project = 'LuaMacro'
+format = 'markdown'
+new_type("macro","Macros")
+output = 'api'
+alias("p","param")
+file = {
+ 'macro.lua','macro','luam.lua',
+}
diff --git a/Tools/LuaMacro/docgen b/Tools/LuaMacro/docgen new file mode 100644 index 0000000..f8765d3 --- /dev/null +++ b/Tools/LuaMacro/docgen @@ -0,0 +1,3 @@ +ldoc .
+lua markdown.lua readme.md
+cp readme.html docs/index.html
diff --git a/Tools/LuaMacro/docgen.bat b/Tools/LuaMacro/docgen.bat new file mode 100644 index 0000000..509bc1f --- /dev/null +++ b/Tools/LuaMacro/docgen.bat @@ -0,0 +1 @@ +ldoc . && lua ..\winapi\markdown.lua readme.md && copy readme.html docs\index.html
diff --git a/Tools/LuaMacro/luam b/Tools/LuaMacro/luam new file mode 100644 index 0000000..bd02269 --- /dev/null +++ b/Tools/LuaMacro/luam @@ -0,0 +1,280 @@ +#!/usr/bin/env lua +--[[-- +Front end for LuaMacro, a Lua macro preprocessor. + +The default action is to preprocess and run a Lua file. To just dump +the preprocessed output, use the `-d` flag. Like `lua`, the `-l` flag can +be used to load a library first, but you need to explicitly say `-i` to +get an interactive prompt. + +The package loader is modified so that `require 'mod'` will preprocess `mod` if it is found as `mod.m.lua`. + +Dumping is the only action available when preprocessing C code with `-C`. + +@script luam +]] + +-- adjust the path so that this script can see the macro package +local path = arg[0]:gsub('[^/\\]+$','') +package.path = package.path .. ';' .. path .. '?.lua;'..path .. 'macro/?.lua' +local macro = require 'macro' +require 'macro.builtin' + +--- Using luam. +-- @usage follows +local usage = [[ +LuaMacro 2.5.0, a Lua macro preprocessor and runner + -l require a library + -e statement to be executed + -V set a variable (-VX or -VY=1) + -c error context to be shown (default 2) + -d dump preprocessed output to stdout + -o write to this file + -C C lexer + -N No #line directives when generating C + -i interactive prompt + -v verbose error trace + <input> Lua source file +]] + +-- parsing the args, the hard way: +local takes_value = {l = '', e = '', c = 2, o = '',V = ';'} + +local args = {} +local idx,i = 1,1 +while i <= #arg do + local a = arg[i] + local flag = a:match '^%-(.+)' + local val + if flag then + if #flag > 1 then -- allow for -lmod, like Lua + val = flag:sub(2) + flag = flag:sub(1,1) + end + -- grab the next argument if we need a value + if takes_value[flag] and not val then + i = i + 1 + val = arg[i] + end + -- convert the argument, if required + local def = takes_value[flag] + if type(def) == 'number' then + val = tonumber(val) + elseif def == ';' and args[flag] then + val = args[flag]..';'..val + end + args[flag] = val or true + else + args[idx] = a + idx = idx + 1 + end + i = i + 1 +end + +if not args[1] and not args.i then + print(usage) + os.exit() +elseif args[1] then + args.input_name = args[1] + args.input,err = io.open(args[1],'r') + if err then return print(err) end + table.remove(args,1) +end +-- set defaults, if flags not specified +for k,v in pairs(takes_value) do + if not args[k] then + args[k] = v + end +end + +---------- compiling and running the output ------ +-- the tricky bit here is presenting the errors so that they refer to the +-- original line numbers. In addition, we also present a few lines of context +-- in the output. + +local function lookup_line (lno,li) + for i = 1,#li-1 do + --print(li[i].il,li[i].ol,lno,'match') + if lno < li[i+1].ol then + return li[i].il + (lno - li[i].ol) - 1 + end + end + return li[#li].il + (lno - li[#li].ol) - 1 +end + +-- iterating over all lines in a string can be awkward; +-- gmatch doesn't handle the empty-line cases properly. +local function split_nl (t) + local k1 = 1 + local k2 = t:find ('[\r\n]',k1) + return function() + if not k2 then return nil end + local res = t:sub(k1,k2-1) + k1 = k2+1 + k2 = t:find('[\r\n]',k1) + return res + end +end + +local function fix_error_trace (err,li) + local strname,lno = err:match '%[string "(%S+)"%]:(%d+)' + local ino + if strname then + lno = tonumber(lno) + if li then + ino = lookup_line(lno,li) + err = err:gsub('%[string "%S+"%]:'..(lno or '?')..':',strname..':'..(ino or '?')) + end + end + return err,lno,ino +end + +local function runstring (code,name,li,...) + local res,err = loadstring(code,name) + local lno,ok + if not res then + err,lno,ino = fix_error_trace(err,li) + if ino then + print 'preprocessed context of error:' + local l1,l2 = lno-args.c,lno+args.c + local l = 1 + for line in split_nl(code) do + if l >= l1 and l <= l2 then + if l == lno then io.write('*') else io.write(' ') end + print(l,line) + end + l = l + 1 + end + end + io.stderr:write(err,'\n') + os.exit(1) + end + ok,err = xpcall(function(...) return res(...) end, debug.traceback) + if not ok then + err = err:gsub("%[C%]: in function 'xpcall'.+",'') + if li then + repeat + err,lno = fix_error_trace(err,li) + until not lno + end + io.stderr:write(err,'\n') + end + return ok +end + +local function subst (ins,name) + local C + if args.C then + C = args.N and true or 'line' + end + return macro.substitute_tostring(ins,name,C,args.v) +end + +local function subst_runstring (ins,name,...) + local buf,li = subst(ins,name) + if not buf then + io.stderr:write(li,'\n') + os.exit(1) + end + if args.d or args.C or args.o ~= '' then + if args.o == '' then + print(buf) + else + local f = io.open(args.o,'w') + f:write(buf) + f:close() + end + else + return runstring(buf,name,li,...) + end +end + +-- Lua 5.1/5.2 compatibility +local pack = table.pack +if not pack then + function pack(...) + return {n=select('#',...),...} + end +end +if not unpack then unpack = table.unpack end + +local function eval(code) + local status,val,f,err,rcnt + code,rcnt = code:gsub('^%s*=','return ') + f,err = loadstring(code,'TMP') + if f then + res = pack(pcall(f)) + if not res[1] then err = res[2] + else + return res + end + end + if err then + err = tostring(err):gsub('^%[string "TMP"%]:1:','') + return {nil,err} + end +end + +local function interactive_loop () + os.execute(arg[-1]..' -v') -- for the Lua copyright + print 'Lua Macro 2.5.0 Copyright (C) 2007-2011 Steve Donovan' + + local function readline() + io.write(_PROMPT or '> ') + return io.read() + end + + require 'macro.all' + _G.macro = macro + macro.define 'quit os.exit()' + macro._interactive = true + + local line = readline() + while line do + local s,err = subst(line..'\n') + if not s then + err = err:gsub('.-:%d+:','') + print('macro error: '..err) + elseif not s:match '^%s*$' then + if args.d then print(s) end + local res = eval(s) + if not res[1] then + print('expanded: '..s) + print('error: '..res[2]) + elseif res[2] ~= nil then + print(unpack(res,2)) + end + end + line = readline() + end +end + +macro.set_package_loader() + +if args.l ~= '' then require(args.l) end + +if args.V ~= ';' then + for varset in args.V:gmatch '([^;]+)' do + local sym,val = varset:match '([^=]+)=(.+)' + if not sym then + sym = varset + val = true + end + _G[sym] = val + end +end + +require 'macro.ifelse' + +if args.e ~= '' then + subst_runstring(args.e,"<temp>") +else + if args.input then + arg = args + arg[0] = args.input_name + arg[-1] = 'luam' + subst_runstring(args.input,args.input_name,unpack(args)) + elseif args.i then + interactive_loop() + end +end diff --git a/Tools/LuaMacro/macro.lua b/Tools/LuaMacro/macro.lua new file mode 100644 index 0000000..6c1a38d --- /dev/null +++ b/Tools/LuaMacro/macro.lua @@ -0,0 +1,713 @@ +---------------------------------------------- +-- LuaMacro 2, a macro-preprocessor for Lua. +-- Unlike LuaMacro 1.x, it does not depend on the token-filter patch and generates +-- Lua code which can be printed out or compiled directly. C-style macros are easy, but LM2 +-- allows for macros that can read their own input and generate output using Lua code. +-- New in this release are lexically-scoped macros. +-- The Lua Lpeg Lexer is by Peter Odding. +-- +-- Examples: +-- +-- macro.define 'sqr(x) ((x)*(x))' +-- macro.define 'assert_(expr) assert(expr,_STR_(expr))' +-- macro.define('R(n)',function(n) +-- n = n:get_number() +-- return ('-'):rep(n) +-- end +-- macro.define('lazy',function(get) +-- get() -- skip space +-- local expr,endt = get:upto(function(t,v) +-- return t == ',' or t == ')' or t == ';' +-- or (t=='space' and v:match '\n') +-- end) +-- return 'function(_) return '..tostring(expr)..' end'..tostring(endt) +-- end) +-- +-- +-- @author Steve Donovan +-- @copyright 2011 +-- @license MIT/X11 +-- @module macro +-- @alias M + +local macro = {} +local M = macro +local lexer = require 'macro.lexer' +local Getter = require 'macro.Getter' +local TokenList = require 'macro.TokenList' +local scan_code = lexer.scan_lua +local append = table.insert +local setmetatable = setmetatable + +--local tdump = require 'pl.pretty'.dump + +local scan_iter, tnext = Getter.scan_iter, Getter.next + + +M.upto_keywords = Getter.upto_keywords +M.Putter = TokenList.new + +-- given a token list, a set of formal arguments and the actual arguments, +-- return a new token list where the formal arguments have been replaced +-- by the actual arguments +local function substitute_tokenlist (tl,parms,args) + local append,put_tokens = table.insert,TokenList.tokens + local parm_map = {} + for i,name in ipairs(parms) do + parm_map[name] = args[i] + end + local res = {} + for _,tv in ipairs(tl) do + local t,v = tv[1],tv[2] + if t == 'iden' then + local pval = parm_map[v] + if pval then + put_tokens(res,pval) + else + append(res,tv) + end + else + append(res,tv) + end + end + return res +end + +---------------- +-- Defining and Working with Macros. +-- @section macros + +--- make a copy of a list of tokens. +-- @param tok the list +-- @param pred copy up to this condition; if defined, must be a function +-- of two arguments, the token type and the token value. +-- @return the copy +-- @return the token that matched the predicate +function M.copy_tokens(tok,pred) + local res = {} + local t,v = tok() + while t and not (pred and pred(t,v)) do + append(res,{t,v}) + t,v = tok() + end + return res,{t,v} +end + +---- define new lexical tokens. +-- @param extra a list of strings defining the new tokens +-- @usage macro.define_tokens{'{|'} +function M.define_tokens(extra) + lexer.add_extra_tokens(extra) +end + +local imacros,smacros = {},{} + +M.macro_table = imacros + +--- define a macro using a specification string and optional function. +-- The specification looks very much like a C preprocessor macro: the name, +-- followed by an optional formal argument list (_no_ space after name!) and +-- the substitution. e.g `answer 42` or `sqr(x) ((x)*(x))` +-- +-- If there is no substitution, then the second argument must be a function which +-- will be evaluated for the actual substitution. If there are explicit parameters, then they will be passed as token lists. Otherwise, the function is passed a `get` and a `put` argument, which are `Getter` and `TokenList` objects. +-- +-- The substitution function may return a `TokenList` object, or a string. +-- @param macstr +-- @param subst_fn the optional substitution function +-- @see macro.Getter, macro.TokenList +function M.define(macstr,subst_fn) + local tok,t,macname,parms,parm_map + local mtbl + tok = scan_code(macstr) + t,macname = tok() + if t == 'iden' then mtbl = imacros + elseif t ~= 'string' and t ~= 'number' and t ~= 'keyword' then + mtbl = smacros + else + error("a macro cannot be of type "..t) + end + t = tok() + if t == '(' then + parms = Getter.new(tok):idens() + end + mtbl[macname] = { + name = macname, + subst = subst_fn or M.copy_tokens(tok), + parms = parms + } +end + +--- define a macro using a function and a parameter list. +-- @param name either an identifier or an operator. +-- @param subst a function +-- @param parms a list of parameter names +-- @return the existing value of this macro, if any +function M.set_macro(name,subst,parms) + local macros + if name:match '^[_%a][_%w]*$' then + macros = imacros + else + macros = smacros + end + if subst == nil then + macros[name] = nil + return + end + local last = macros[name] + if type(subst) ~= 'table' or not subst.name then + subst = { + name = name, + subst = subst, + parms = parms + } + end + macros[name] = subst + return last +end + +--- defined a scoped macro. Like define except this macro will not +-- be visible outside the current scope. +-- @param name either an identifier or an operator. +-- @param subst a function +-- @param parms a list of parameter names +-- @see set_macro +function M.define_scoped (name,subst,parms) + local old_value = M.set_macro(name,subst,parms) + M.block_handler(-1,function() + M.set_macro(name,old_value) + end) +end + +--- get the value of a macro. The macro substitution must either be a +-- a string or a single token. +-- @param name existing macro name +-- @return a string value, or nil if the macro does not exist. +function M.get_macro_value(name) + local mac = imacros[name] + if not mac then return nil end + if type(mac.subst) == 'table' then + return mac.subst[1][2] + else + return mac.subst + end +end + +local function get_macro (mac, no_error) + local macro = imacros[mac] + if not macro and not no_error then + M.error("macro "..mac.." is not defined") + end + return macro +end + +local push,pop = table.insert,table.remove + +--- push a value on the stack associated with a macro. +-- @param name macro name +-- @param value any value +function M.push_macro_stack (name,value) + local macro = get_macro(name) + macro.stack = macro.stack or {} + push(macro.stack,value) +end + +--- pop a value from a macro stack. +-- @param name macro name +-- @return any value, if defined +function M.pop_macro_stack (name) + local macro = get_macro(name) + if macro.stack and #macro.stack > 0 then + return pop(macro.stack) + end +end + +--- value of top of macro stack. +-- @param name macro name +-- @return any value, if defined +function M.value_of_macro_stack (name) + local macro = get_macro(name,true) + if not macro then return nil end + if macro.stack and #macro.stack > 0 then + return macro.stack[#macro.stack] + end +end + +local lua_keywords = { + ['do'] = 'open', ['then'] = 'open', ['else'] = 'open', ['function'] = 'open', + ['repeat'] = 'open'; + ['end'] = 'close', ['until'] = 'close',['elseif'] = 'close' +} + +local c_keywords = {} +local keywords = lua_keywords + +local block_handlers,keyword_handlers = {},{} +local level = 1 + +--- specify a block handler at a given level. +-- a block handler may indicate with an extra true return +-- that it wants to persist; it is passed the getter and the keyword +-- so we can get more specific end-of-block handlers. +-- @param lev relative block level +-- @param action will be called when the block reaches the level +function M.block_handler (lev,action) + lev = lev + level + if not block_handlers[lev] then + block_handlers[lev] = {} + end + append(block_handlers[lev],action) +end + +local function process_block_handlers(level,get,v) + local persist,result + for _,bh in pairs(block_handlers[level]) do + local res,keep = bh(get,v) + if not keep then + if res then result = res end + else + persist = persist or {} + append(persist,bh) + end + end + block_handlers[level] = persist + return result +end + + +--- set a keyword handler. Unlike macros, the keyword itself is always +-- passed through, but the handler may add some output afterwards. +-- If the action is nil, then the handler for that keyword is removed. +-- @param word keyword +-- @param action function to be called when keyword is encountered +-- @return previous handler associated with this keyword +function M.keyword_handler (word,action) + if word == 'BEGIN' or word == 'END' then + keyword_handlers[word] = action + return + end + if action then + local last = keyword_handlers[word] + keyword_handlers[word] = action + return last + else + keyword_handlers[word] = nil + end +end + +--- set a scoped keyword handler. Like keyword_handler, except +-- it restores the original keyword handler (if any) at the end +-- of the current block. +-- @param word keyword +-- @param action to be called when keyword is encountered +-- @see keyword_handler +function M.scoped_keyword_handler (keyword, action) + local last = M.keyword_handler(keyword,action) + M.block_handler(-1,function() + M.keyword_handler(keyword,last) + end) +end + +-- a convenient way to use keyword handlers. This sets a handler and restores +-- the old handler at the end of the current block. +-- @param word keyword +-- @param action to be called when keyword is encountered +-- @return a function that creates a scoped keyword handler +function M.make_scoped_handler(keyword,handler) + return function() M.scoped_keyword_handler(keyword, action) end +end + +M.please_throw = false + +--- macro error messages. +-- @param msg the message: will also have file:line. +function M.error(msg) + msg = M.filename..':'..lexer.line..': '..msg + if M.please_throw then + error(msg,2) + else + io.stderr:write(msg,'\n') + os.exit(1) + end +end + +M.define ('debug_',function() + M.DEBUG = true +end) + +--- macro error assert. +-- @param expr an expression. +-- @param msg a message +function M.assert(expr,msg) + if not expr then M.error(msg or 'internal error') end + return expr +end + +Getter.error = M.error +Getter.assert = M.assert +TokenList.assert = M.assert + +local line_updater, line_table, last_name, last_lang + +local function lua_line_updater (iline,oline) + if not line_table then line_table = {} end + append(line_table,{il=iline,ol=oline}) +end + +local function c_line_updater (iline,oline,last_t,last_v) + local endt = last_t == 'space' and last_v or '\n' + return '#line '..iline..' "'..M.filename..'"'..endt +end + +local make_putter = TokenList.new + +--- do a macro substitution on Lua source. +-- @param src Lua source (either string or file-like reader) +-- @param out output (a file-like writer) +-- @param name input file name +-- @param use_c nil for Lua; if 'line', then output #line directives; if true, then don't +-- @return the result as table of strings +-- @return line number information +function M.substitute(src,name, use_c) + local out, ii = {}, 1 + local subparse + if name then + last_name = name + last_lang = use_c + else + name = last_name + use_c = last_lang and true + subparse = true + end + M.filename = name + if use_c then + lexer = require 'macro.clexer' + scan_code = lexer.scan_c + keywords = c_keywords + if use_c == 'line' then + line_updater = c_line_updater + else + line_updater = function() end + end + else + lexer = require 'macro.lexer' + scan_code = lexer.scan_lua + keywords = lua_keywords + line_updater = lua_line_updater + end + local tok = scan_code(src,name) + local iline,iline_changed = 0 + local last_t,last_v = 'space','\n' + local do_action + + + local t,v = tok() + + -- this function get() is always used, so that we can handle end-of-stream properly. + -- The substitution mechanism pushes a new stream on the tstack, which is popped + -- when empty. + local tstack = {} + local push,pop = table.insert,table.remove + + local function get () + last_t,last_v = t,v + local t,v = tok() + while not t do + tok = pop(tstack) + if tok == nil then + if not subparse and keyword_handlers.END then + do_action(keyword_handlers.END) + keyword_handlers.END = nil + end + if tok == nil then -- END action might have inserted some tokens + return nil + end + end -- finally finished + t,v = tok() + end + if name == lexer.name and iline ~= lexer.line then + iline = lexer.line -- input line has changed + iline_changed = last_v + end + return t,v + end + + local getter = Getter.new(get) + + --- get a list of consecutive matching tokens. + -- @param get token fetching function + -- @param accept set of token types (default: `{space=true,comment=true}`) + function getter.matching (get, accept) + accept = accept or {space=true, comment=true} + local tl = TokenList.new() + local t,v = get:peek(1, true) + while accept[t] do + t,v = get () + append(tl, {t, v}) + t,v = get:peek(1, true) + end + return tl + end + + function getter:peek (offset,dont_skip) + local step = offset < 0 and -1 or 1 -- passing offset 0 is undefined + local k = 0 + local token, t, v + repeat + while true do + token = tok (k) + if not token then return nil, 'EOS' end + t,v = token[1], token[2] + if dont_skip or (t ~= 'space' and t ~= 'comment') then break end + k = k + 1 + end + offset = offset - step + k = k + step + until offset == 0 + return t,v,k+1 + end + + function getter:peek2 () + local t1,v1,k1 = self:peek(1) + local t2,v2 = self:peek(k1+1) + return t1,v1,t2,v2 + end + + function getter:patch (idx,text) + out[idx] = text + end + + function getter:placeholder (put) + put:iden '/MARK?/' + return ii + end + + function getter:copy_from (pos,clear) + local res = {} + for i = pos, ii do + if out[i] and not out[i]:match '^#line' then + append(res,out[i]) + end + end + if clear then + for i = pos, ii do + table.remove(out,pos) + ii = ii - 1 + end + end + return table.concat(res) + end + + -- this feeds the results of a substitution into the token stream. + -- substitutions may be token lists, Lua strings or nil, in which case + -- the substitution is ignored. The result is to push a new token stream + -- onto the tstack, so it can be fetched using get() above + local function push_substitution (subst) + if subst == nil then return end + local st = type(subst) + push(tstack,tok) + if st == 'table' then + subst = scan_iter(subst) + elseif st == 'string' then + subst = scan_code(subst) + end + tok = subst + end + M.push_substitution = push_substitution + + -- a macro object consists of a subst object and (optional) parameters. + -- If there are parms, then a macro argument list must follow. + -- The subst object is either a token list or a function; if a token list we + -- substitute the actual parameters for the formal parameters; if a function + -- then we call it with the actual parameters. + -- Without parameters, it may be a simple substitution (TL or Lua string) or + -- may be a function. In the latter case we call it passing the token getter, + -- assuming that it will grab anything it needs from the token stream. + local function expand_macro(get,mac) + local pass_through + local subst = mac.subst + local fun = type(subst)=='function' + if mac.parms then + t = tnext(get); + if t ~= '(' then + M.error('macro '..mac.name..' expects parameters') + end + local args,err = Getter.list(get) + M.assert(args,'no end of argument list') + if fun then + subst = subst(unpack(args)) + else + if #mac.parms ~= #args then + M.error(mac.name.." takes "..#mac.parms.." arguments") + end + subst = substitute_tokenlist(subst,mac.parms,args) + end + elseif fun then + subst,pass_through = subst(getter,make_putter()) + end + push_substitution(subst) + return pass_through + end + + local multiline_tokens,sync = lexer.multiline_tokens,lexer.sync + local line,last_diff = 0,0 + + function do_action (action) + push_substitution(action(getter,make_putter())) + end + + if not subparse and keyword_handlers.BEGIN then + do_action(keyword_handlers.BEGIN) + end + + while t do + --print('tv',t,v) + local dump = true + if t == 'iden' then -- classic name macro + local mac = imacros[v] + if mac then + dump = expand_macro(get,mac) + end + elseif t == 'keyword' then + -- important to track block level for lexical scoping and block handlers + local class = keywords[v] + if class == 'open' then + if v ~= 'else' then level = level + 1 end + elseif class == 'close' then + level = level - 1 + if block_handlers[level] then + local res = process_block_handlers(level,get,v) + if res then push_substitution(res) end + end + --* elseif class == 'hook' then + end + local action = keyword_handlers[v] + if action then do_action(action) end + else -- any unused 'operator' token (like @, \, #) can be used as a macro + if use_c then + if v == '{' then + level = level + 1 + elseif v == '}' then + level = level - 1 + if block_handlers[level] then + local res = process_block_handlers(level,get,v) + if res then push_substitution(res) end + end + end + end + local mac = smacros[v] + if mac then + dump = expand_macro(get,mac) + end + end + if dump then + if multiline_tokens[t] then -- track output line + line = sync(line, v) + end + if iline_changed then + local diff = line - iline + if diff ~= last_diff then + local ldir = line_updater(iline,line,last_t,last_v) + if ldir then out[ii] = ldir; ii=ii+1 end + last_diff = diff + end + iline_changed = nil + end + out[ii] = v + ii = ii + 1 + end + t,v = get() + end + + return out,line_table +end + +--- take some Lua source and return the result of the substitution. +-- Does not raise any errors. +-- @param src either a string or a readable file object +-- @param name optional name for the chunk +-- @return the result or nil +-- @return the error, if error +function M.substitute_tostring(src,name,use_c,throw) + M.please_throw = true + local ok,out,li + if throw then + out,li = M.substitute(src,name,use_c) + else + ok,out,li = pcall(M.substitute,src,name,use_c) + end + if type(src) ~= 'string' and src.close then src:close() end + if not ok then return nil, out + else + return table.concat(out), li + end +end + +local lua52 = _VERSION:match '5.2' +local load, searchpath = load, package.searchpath + +if not lua52 then -- Lua 5.1 + function load (env,src,name) + local chunk,err = loadstring(src,name) + if chunk and env then + setfenv(chunk,env) + end + return chunk,err + end +end + +if not searchpath then + local sep = package.config:sub(1,1) + searchpath = function (mod,path) + mod = mod:gsub('%.',sep) + for m in path:gmatch('[^;]+') do + local nm = m:gsub('?',mod) + local f = io.open(nm,'r') + if f then f:close(); return nm end + end + end +end + +--- load Lua code in a given envrionment after passing +-- through the macro preprocessor. +-- @param src either a string or a readable file object +-- @param name optional name for the chunk +-- @param env the environment (may be nil) +-- @return the cnunk, or nil +-- @return the error, if no chunk +function M.load(src,name,env) + local res,err = M.substitute_tostring(src,'tmp') + if not res then return nil,err end + return loadin(env,res,name) +end + +--- evaluate Lua macro code in a given environment. +-- @param src either a string or a readable file object +-- @param env the environment (can be nil) +-- @return true if succeeded +-- @return result(s) +function M.eval(src,env) + local chunk,err = M.loadin(src,'(tmp)',env) + if not chunk then return nil,err end + return pcall(chunk) +end + +package.mpath = './?.m.lua' + +--- Make `require` use macro expansion. +-- This is controlled by package.mpath, which is initially './?.m.lua' +function M.set_package_loader() + -- directly inspired by https://github.com/bartbes/Meta/blob/master/meta.lua#L32, + -- after a suggestion by Alexander Gladysh + table.insert(package.loaders, function(name) + local fname = searchpath(name,package.mpath) + if not fname then return nil,"cannot find "..name end + local res,err = M.load(io.open(fname),lname) + if not res then + error (err) + end + return res + end) +end + +return macro diff --git a/Tools/LuaMacro/macro/Getter.lua b/Tools/LuaMacro/macro/Getter.lua new file mode 100644 index 0000000..af58b3c --- /dev/null +++ b/Tools/LuaMacro/macro/Getter.lua @@ -0,0 +1,320 @@ +--- Getter class. Used to get values from the token stream. The first +-- argument `get` of a macro substitution function is of this type. +-- +-- M.define ('\\',function(get,put) +-- local args, body = get:idens('('), get:list() +-- return put:keyword 'function' '(' : idens(args) ')' : +-- keyword 'return' : list(body) : space() : keyword 'end' +-- end) +-- +-- The second argument `put` is a `TokenList` object. +-- @see macro.TokenList +-- @module macro.Getter + +local TokenList = require 'macro.TokenList' +local append = table.insert +local setmetatable = setmetatable + +local Getter = { + __call = function(self) + return self.fun() + end +} +local M = Getter + +Getter.__index = Getter; + +local scan_iter + +function Getter.new (get) + return setmetatable({fun=get},Getter) +end + +function Getter.from_tl(tl) + return Getter.new(scan_iter(tl)) +end + +local Tok = { + __tostring = function(self) + return self[2] + end +} + +local function tok_new (t) + return setmetatable(t,Tok) +end + +-- create a token iterator out of a token list +function Getter.scan_iter (tlist) + local i,n = 1,#tlist + return function(k) + if k ~= nil then + k = i + k + if k < 1 or k > n then return nil end + return tlist[k] + end + local tv = tlist[i] + if tv == nil then return nil end + i = i + 1 + return tv[1],tv[2] + end +end + +scan_iter = Getter.scan_iter + +--- get the next non-whitespace token. +-- @return token type +-- @return token value +-- @function Getter.next +function Getter.next(get) + local t,v = get() + while t == 'space' or t == 'comment' do + t,v = get() + end + return t,v +end + +local TL,LTL = TokenList.new, TokenList.new_list + + +local function tappend (tl,t,val) + val = val or t + append(tl,{t,val}) +end + +--- get a balanced block. +-- Typically for grabbing up to an `end` keyword including any nested +-- `if`, `do` or `function` blocks with their own `end` keywords. +-- @param tok the token stream +-- @param begintokens set of tokens requiring their own nested *endtokens* +-- (default: `{['do']=true,['function']=true,['if']=true}`) +-- @param endtokens set of tokens ending a block (default:`{['end']=true}`) +-- @return list of tokens +-- @return block end token in form `{type,value}` +-- @usage +-- -- copy a balanced table constructor +-- get:expecting '{' +-- put '{':tokens (get:block ({['{']=true}, {['}']=true}) '}') +function Getter.block(tok,begintokens,endtokens) + begintokens = begintokens or {['do']=true,['function']=true,['if']=true} + endtokens = endtokens or {['end']=true} + local level = 1 -- used to count expected matching `endtokens` + local tl = TL() + local token,value + repeat + token,value = tok() + if not token then return nil,'unexpected end of block' end + if begintokens[value] then + level = level + 1 + elseif endtokens[value] then + level = level - 1 + end + if level > 0 then -- final end token is returned separately + tappend(tl,token,value) + end + until level == 0 + return tl,tok_new{token,value} +end + +--- get a delimited list of token lists. +-- Typically used for grabbing argument lists like ('hello',a+1,fred(c,d)); will count parens +-- so that the delimiter (usually a comma) is ignored inside sub-expressions. You must have +-- already read the start token of the list, e.g. open parentheses. It will eat the end token +-- and return the list of TLs, plus the end token. Based on similar code in Penlight's +-- `pl.lexer` module. +-- @param tok the token stream +-- @param endt the end token (default ')') +-- @param delim the delimiter (default ',') +-- @return list of token lists +-- @return end token in form {type,value} +function Getter.list(tok,endtoken,delim) + endtoken = endtoken or ')' + delim = delim or ',' + local parm_values = LTL() + local level = 1 -- used to count ( and ) + local tl = TL() + local is_end + if type(endtoken) == 'function' then + is_end = endtoken + elseif endtoken == '\n' then + is_end = function(t,val) + return t == 'space' and val:find '\n' + end + else + is_end = function (t) + return t == endtoken + end + end + local token,value = tok() + if is_end(token,value) then return parm_values end + if token == 'space' then + token,value = tok() + end + while true do + if not token then return nil,'unexpected end of list' end -- end of stream is an error! + if is_end(token,value) and level == 1 then + append(parm_values,tl) + break + elseif token == '(' then + level = level + 1 + tappend(tl,'(') + elseif token == ')' then + level = level - 1 + if level == 0 then -- finished with parm list + append(parm_values,tl) + break + else + tappend(tl,')') + end + elseif token == '{' then + level = level + 1 + tappend(tl,'{') + elseif token == '}' then + level = level - 1 + tappend(tl,'}') + elseif token == delim and level == 1 then + append(parm_values,tl) -- a new parm + tl = TL() + else + tappend(tl,token,value) + end + token,value=tok() + end + return parm_values,tok_new{token,value} +end + +function Getter.upto_keywords (k1,k2) + return function(t,v) + return t == 'keyword' and (v == k1 or v == k2) + end,'' +end + +local tnext = Getter.next + + +function Getter.upto(tok,k1,k2) + local endt = k1 + if type(k1) == 'string' and k1:match '^%a+$' then + endt = Getter.upto_keywords(k1,k2) + end + local ltl,tok = tok:list(endt,'') + M.assert(ltl ~= nil and #ltl > 0,'failed to grab tokens') + return ltl[1],tok +end + +function Getter.line(tok) + return tok:upto(function(t,v) + return (t=='space' and v:match '\n') or t == 'comment' + end) +end + + +local function prettyprint (t, v) + v = v:gsub ("\n", "\\n") + if t == "string" then + if #v > 16 then v = v:sub(1,12).."..."..v:sub(1,1) end + return t.." "..v + end + if #v > 16 then v = v:sub(1,12).."..." end + if t == "space" or t == "comment" or t == "keyword" then + return t.." '"..v.."'" + elseif t == v then + return "'"..v.."'" + else + return t.." "..v + end +end + +--- get the next identifier token. +-- (will be an error if the token has wrong type) +-- @return identifier name +function Getter.iden(tok) + local t,v = tnext(tok) + M.assert(t == 'iden','expecting identifier, got '..prettyprint(t,v)) + return v +end + +Getter.name = Getter.iden -- backwards compatibility! + +--- get the next number token. +-- (will be an error if the token has wrong type) +-- @return converted number +function Getter.number(tok) + local t,v = tnext(tok) + M.assert(t == 'number','expecting number, got '..prettyprint(t,v)) + return tonumber(v) +end + +--- get a delimited list of identifiers. +-- works like list. +-- @param tok the token stream +-- @param endt the end token (default ')') +-- @param delim the delimiter (default ',') +-- @see list +function Getter.idens(tok,endt,delim) + local ltl,err = tok:list(endt,delim) + if not ltl then error('idens: '..err) end + local names = {} + -- list() will return {{}} for an empty list of tlists + for i = 1,#ltl do + local tl = ltl[i] + local tv = tl[1] + if tv then + if tv[1] == 'space' then tv = tl[2] end + names[i] = tv[2] + end + end + return names, err +end + +Getter.names = Getter.idens -- backwards compatibility! + +--- get the next string token. +-- (will be an error if the token has wrong type) +-- @return string value (without quotes) +function Getter.string(tok) + local t,v = tok:expecting("string") + return v:sub(2,-2) +end + +--- assert that the next token has the given type. This will throw an +-- error if the next non-whitespace token does not match. +-- @param type a token type ('iden','string',etc) +-- @param value a token value (optional) +-- @usage get:expecting '(' +-- @usage get:expecting ('iden','bonzo') +function Getter.expecting (tok,type,value) + local t,v = tnext(tok) + if t ~= type then M.error ("expected "..type.." got "..prettyprint(t,v)) end + if value then + if v ~= value then M.error("expected "..value.." got "..prettyprint(t,v)) end + end + return t,v +end + +--- peek ahead or before in the token stream. +-- @param k positive delta for looking ahead, negative for looking behind. +-- @param dont_skip true if you want to check for whitespace +-- @return the token type +-- @return the token value +-- @return the token offset +-- @function Getter.peek + +--- peek ahead two tokens. +-- @return first token type +-- @return first token value +-- @return second token type +-- @return second token value +-- @function Getter.peek2 + +--- patch the token stream at the end. +-- @param idx index in output table +-- @param text to replace value at that index +-- @function Getter.patch + +--- put out a placeholder for later patching. +-- @param put a putter object +-- @return an index into the output table +-- @function Getter.placeholder + +return Getter diff --git a/Tools/LuaMacro/macro/TokenList.lua b/Tools/LuaMacro/macro/TokenList.lua new file mode 100644 index 0000000..a18ac67 --- /dev/null +++ b/Tools/LuaMacro/macro/TokenList.lua @@ -0,0 +1,201 @@ +--------------- +-- A TokenList class for generating token lists. +-- +-- There are also useful `get_` methods for extracting values from +-- the first token. +-- +-- @module macro.TokenList + +local TokenList = {} +local M = TokenList +TokenList.__index = TokenList + +local append = table.insert + +function TokenList.new (tl) + return setmetatable(tl or {},TokenList) +end + +local TokenListList = {} + +function TokenList.new_list (ltl) + return setmetatable(ltl or {},TokenListList) +end + +TokenListList.__index = function(self,key) + local m = TokenList[key] + return function(self,...) + local res = {} + for i = 1,#self do res[i] = m(self[i],...) end + return TokenList.new_list(res) + end +end + +-- token-getting helpers + + +local function extract (tl) + local tk = tl[1] + if tk[1] == 'space' then + tk = tl[2] + end + return tk +end + +--- get an identifier from front of a token list. +-- @return identifier name +function TokenList.get_iden (tl) + local tk = extract(tl) + M.assert(tk[1]=='iden','expecting identifier') + return tk[2] +end + +--- get an number from front of a token list. +-- @return number +function TokenList.get_number(tl) + local tk = extract(tl) + M.assert(tk[1]=='number','expecting number') + return tonumber(tk[2]) +end + +--- get a string from front of a token list. +-- @return string value (without quotes) +function TokenList.get_string(tl) + local tk = extract(tl) + M.assert(tk[1]=='string') + return tk[2]:sub(2,-2) -- watch out! what about long string literals?? +end + +--- takes a token list and strips spaces and comments. +-- @return new tokenlist +function TokenList.strip_spaces (tl) + local out = TokenList.new() + for _,t in ipairs(tl) do + if t[1] ~= 'comment' and t[1] ~= 'space' then + append(out,t) + end + end + return out +end + +--- pick the n-th token from this tokenlist. +-- Note that it returns the value and type, not the type and value. +-- @param n (1 to #self) +-- @return token value +-- @return token type +function TokenList.pick (tl,n) + local t = tl[n] + return t[2],t[1] +end + +-- token-putting helpers +local comma,space = {',',','},{'space',' '} + +--- append an identifier. +-- @param name the identifier +-- @param no_space true if you don't want a space after the iden +-- @return self +function TokenList.iden(res,name,no_space) + append(res,{'iden',name}) + if not no_space then + append(res,space) + end + return res +end + +TokenList.name = TokenList.iden -- backwards compatibility! + +--- append a string. +-- @param s the string +-- @return self +function TokenList.string(res,s) + append(res,{'string','"'..s..'"'}) + return res +end + +--- append a number. +-- @param val the number +-- @return self +function TokenList.number(res,val) + append(res,{'number',val}) + return res +end + +--- put out a list of identifiers, separated by commas. +-- @param res output token list +-- @param names a list of identifiers +-- @return self +function TokenList.idens(res,names) + for i = 1,#names do + res:iden(names[i],true) + if i ~= #names then append(res,comma) end + end + return res +end + +TokenList.names = TokenList.idens -- backwards compatibility! + +--- put out a token list. +-- @param res output token list +-- @param tl a token list +-- @return self +function TokenList.tokens(res,tl) + for j = 1,#tl do + append(res,tl[j]) + end + return res +end + +--- put out a list of token lists, separated by commas. +-- @param res output token list +-- @param ltl a list of token lists +-- @return self +function TokenList.list(res,ltl) + for i = 1,#ltl do + res:tokens(ltl[i]) + if i ~= #ltl then append(res,comma) end + end + return res +end + +--- put out a space token. +-- @param res output token list +-- @param space a string containing only whitespace (default ' ') +-- @return self +function TokenList.space(res,space) + append(res,{'space',space or ' '}) + return res +end + +--- put out a keyword token. +-- @param res output token list +-- @param keyw a Lua keyword +-- @param no_space true if you don't want a space after the iden +-- @return self +function TokenList.keyword(res,keyw,no_space) + append(res,{'keyword',keyw}) + if not no_space then + append(res,space) + end + return res +end + +--- convert this tokenlist into a string. +function TokenList.__tostring(tl) + local res = {} + for j = 1,#tl do + append(res,tl[j][2]) + end + return table.concat(res) +end + +--- put out a operator token. This is the overloaded call operator +-- for token lists. +-- @param res output token list +-- @param keyw an operator string +function TokenList.__call(res,t,v) + append(res,{t,v or t}) + return res +end + +return TokenList diff --git a/Tools/LuaMacro/macro/all.lua b/Tools/LuaMacro/macro/all.lua new file mode 100644 index 0000000..0d7c098 --- /dev/null +++ b/Tools/LuaMacro/macro/all.lua @@ -0,0 +1,5 @@ +require 'macro.forall'
+require 'macro.lambda'
+require 'macro.try'
+require 'macro.do'
+
diff --git a/Tools/LuaMacro/macro/assert.lua b/Tools/LuaMacro/macro/assert.lua new file mode 100644 index 0000000..b25daaf --- /dev/null +++ b/Tools/LuaMacro/macro/assert.lua @@ -0,0 +1,74 @@ +--- a simple testing framework. +-- Defines a single statment macro assert_ which has the following syntax: +-- +-- - assert_ val1 == val2 +-- - assert_ val1 > val2 +-- - assert_ val1 < val2 +-- - assert_ val1 matches val2 (using string matching) +-- - assert_ val1 throws val2 (ditto, on exception string) +-- +-- The `==` case has some special forms. If `val2` is `(v1,v2,..)` then +-- it's assumed that the expression `val1` returns multiple values. `==` will +-- also do value equality for plain tables. If `val2` is a number given in +-- %f format (such as 3.14) then it will match `vall` up to that specified +-- number of digits. +-- +-- assert_ {one=1,two=2} == {two=2,one=1} +-- assert_ 'hello' matches '^hell' +-- assert_ 2 > 1 +-- assert_ ('hello'):find 'll' == (3,4) +-- assert_ a.x throws 'attempt to index global' +-- @module macro.assert + +local M = require 'macro' +local relop = { + ['=='] = 'eq', + ['<'] = 'lt', + ['>'] = 'gt' +} + +local function numfmt (x) + local int,frac = x:match('(%d+)%.(%d+)') + if not frac then return nil end + return '%'..#x..'.'..#frac..'f', x +end + +--- assert that two values match the desired relation. +-- @macro assert_ +M.define('assert_',function(get,put) + local testx,tok = get:upto(function(t,v) + return relop[t] or (t == 'iden' and (v == 'matches' or v == 'throws')) + end) + local testy,eos = get:line() + local otesty = testy + testx = tostring(testx) + testy = tostring(testy) + local t,v,op = tok[1],tok[2] + if relop[t] then + op = relop[t] + if t == '==' then + if testy:match '^%(.+%)$' then + testx = 'T_.tuple('..testx..')' + testy = 'T_.tuple'..testy + elseif #otesty == 1 and otesty[1][1] == 'number' then + local num = otesty[1][2] + local fmt,num = numfmt(num) + if fmt then -- explicit floating-point literal + testy = '"'..num..'"' + testx = '("'..fmt..'"):format('..testx..')' + op = 'match' + end + end + end + elseif v == 'matches' then + op = 'match' + elseif v == 'throws' then + op = 'match' + testx = 'T_.pcall_no(function() return '..testx..' end)' + end + return ('T_.assert_%s(%s,%s)%s'):format(op,testx,testy,tostring(eos)) +end) + +return function() + return "T_ = require 'macro.lib.test'" +end diff --git a/Tools/LuaMacro/macro/builtin.lua b/Tools/LuaMacro/macro/builtin.lua new file mode 100644 index 0000000..12c8b38 --- /dev/null +++ b/Tools/LuaMacro/macro/builtin.lua @@ -0,0 +1,161 @@ +------- +-- LuaMacro built-in macros. +-- @module macro.builtin + +local M = require 'macro' + +local function macro_def (scoped) + return function (get) + local t,name,parms,openp + local t,name = get:next() + local upto,ret + if t == '(' then + t,name = get:next() + upto = function(t,v) return t == ')' end + else + upto = function(t,v) + return t == 'space' and v:find '\n' + end + -- return space following (returned by copy_tokens) + ret = true + end + -- might be immediately followed by a parm list + t,openp = get() + if openp == '(' then + parms = get:names() + end + -- the actual substitution is up to the end of the line + local args, space = M.copy_tokens(get,upto) + if scoped then + M.define_scoped(name,args,parms) + else + M.set_macro(name,args,parms) + end + return ret and space[2] + end +end + +--- a macro for defining lexically scoped simple macros. +-- def_ may be followed by an arglist, and the substitution is the +-- rest of the line. +-- @usage def_ block (function() _END_CLOSE_ +-- @usage def_ sqr(x) ((x)*(x)) +-- @macro def_ +M.define ('def_',macro_def(true)) + +--- a global version of `def_`. +-- @see def_ +-- @macro define_ +M.define ('define_',macro_def(false)) + +--- set the value of an existing macro. +-- the name and value follows immediately, and the value must be +-- a single token +-- @usage set_ T 'string' +-- @usage set_ F function +-- @macro set_ +M.define('set_',function(get) + local name = get:name() + local t,v = get:next() + M.set_macro(name,{{t,v}}) +end) + +--- undefining identifier macros. +-- @macro undef_ +M.define('undef_',function(get) + M.set_macro(get:name()) +end) + +--- Insert text after current block end. `_END_` is followed by a quoted string +-- and is used to insert that string after the current block closes. +-- @macro _END_ +M.define ('_END_',function(get) + local str = get:string() + M.block_handler(-1,function(get,word) + if word ~= 'end' then return nil,true end + return str + end) +end) + +--- insert an end after the next closing block. +-- @macro _END_END_ +-- @see _END_ +M.define '_END_END_ _END_ " end"' + +--- insert a closing parens after next closing block. +-- @usage def_ begin (function() _END_CLOSE_ +-- fun begin ... end --> fun (function() ... end) +-- @macro _END_CLOSE_ +-- @see _END_ +M.define '_END_CLOSE_ _END_ ")"' + +--- 'stringizing' macro. +-- Will convert its argument into a string. +-- @usage def_ _assert(x) assert(x,_STR_(x)) +-- @macro _STR_ +M.define('_STR_(x)',function(x) + x = tostring(x) + local put = M.Putter() + return put '"':name(x) '"' +end) + +-- macro stack manipulation + + +--- push a value onto a given macro' stack. +-- @macro _PUSH_ +-- @param mac existing macro name +-- @param V a string +M.define('_PUSH_(mac,V)',function(mac,V) + M.push_macro_stack(mac:get_string(),V:get_string()) +end) + +--- pop a value from a macro's stack. +-- @macro _POP_ +-- @param mac existing macro name +-- @return a string +-- @see _PUSH_ +M.define('_POP_',function(get,put) + local val = M.pop_macro_stack(get:string()) + if val then + return put(val) + end +end) + +--- drop the top of a macro's stack. +-- Like `_POP_`, except that it does not return the value +-- @macro _DROP_ +-- @return existing macro name +-- @see _POP_ +M.define('_DROP_',function(get) + M.pop_macro_stack(get:string()) +end) + +--- Load a Lua module immediately. This allows macro definitions to +-- to be loaded before the rest of the file is parsed. +-- If the module returns a function, then this is assumed to be a +-- substitution function, allowing macro modules to insert code +-- at this point. +-- @macro require_ +M.define('require_',function(get,put) + local name = get:string() + local ok,fn = pcall(require,name) + if not ok then + fn = require('macro.'..name) + end + if type(fn) == 'function' then + return fn(get,put) + end +end) + +--- Include the contents of a file. This inserts the file directly +-- into the token stream, and is equivalent to cpp's `#include` directive. +-- @macro include_ +M.define('include_',function(get) + local str = get:string() + local f = M.assert(io.open(str)) + local txt = f:read '*a' + f:close() + M.push_substitution(txt) +end) + diff --git a/Tools/LuaMacro/macro/clexer.lua b/Tools/LuaMacro/macro/clexer.lua new file mode 100644 index 0000000..fd859a8 --- /dev/null +++ b/Tools/LuaMacro/macro/clexer.lua @@ -0,0 +1,169 @@ +--[[--- A C lexical scanner using LPeg. += CREDITS += based on the C lexer in Peter Odding's lua-lxsh +@module macro.clexer +--]] + +local clexer = {} +local lpeg = require 'lpeg' +local P, R, S, C, Cc, Ct = lpeg.P, lpeg.R, lpeg.S, lpeg.C, lpeg.Cc, lpeg.Ct + +-- create a pattern which captures the lua value [id] and the input matching +-- [patt] in a table +local function token(id, patt) return Ct(Cc(id) * C(patt)) end + +-- private interface +local table_of_tokens +local extra_tokens + +function clexer.add_extra_tokens(extra) + extra_tokens = extra_tokens or {} + for _,t in ipairs(extra) do + table.insert(extra_tokens,t) + end + table_of_tokens = nil -- re-initialize +end + +function clexer.init () + local digit = R('09') + + local upp, low = R'AZ', R'az' + local oct, dec = R'07', R'09' + local hex = dec + R'AF' + R'af' + local letter = upp + low + local alnum = letter + dec + '_' + local endline = S'\r\n\f' + local newline = '\r\n' + endline + local escape = '\\' * ( newline + + S'\\"\'?abfnrtv' + + (#oct * oct^-3) + + ('x' * #hex * hex^-2)) + + + -- range of valid characters after first character of identifier + local idsafe = R('AZ', 'az', '\127\255') + P '_' + + -- operators + local OT = P '==' + if extra_tokens then + for _,ex in ipairs(extra_tokens) do + OT = OT + P(ex) + end + end + local operator = token('operator', OT + P '.' + P'>>=' + '<<=' + '--' + '>>' + '>=' + '/=' + '==' + '<=' + + '+=' + '<<' + '*=' + '++' + '&&' + '|=' + '||' + '!=' + '&=' + '-=' + + '^=' + '%=' + '->' + S',)*%+&(-~/^]{}|.[>!?:=<;') + -- identifiers + local ident = token('iden', idsafe * (idsafe + digit) ^ 0) + + -- keywords + local keyword = token('keyword', (P 'auto' + P 'break' + P 'case' + P'char' + + P 'const' + P 'continue' + P 'default' + + P 'do' + P 'double' + P 'else' + P 'enum' + P 'extern' + P 'float' + + P 'for' + P 'goto' + P 'if' + P 'int' + P 'long' + P 'register' + + P 'return' + P 'short' + P 'signed' + P 'sizeof' + P 'static' + + P 'struct' + P 'switch' + P 'typedef' + P 'union' + P 'void' + + P 'volatile' + P 'while') * -(idsafe + digit)) + + -- numbers + local number_sign = S'+-'^-1 + local number_decimal = digit ^ 1 + local number_hexadecimal = P '0' * S 'xX' * R('09', 'AF', 'af') ^ 1 + local number_float = (digit^1 * P'.' * digit^0 + P'.' * digit^1) * + (S'eE' * number_sign * digit^1)^-1 + local number = token('number', number_hexadecimal + + number_float + + number_decimal) + + + local string = token('string', '"' * ((1 - S'\\\r\n\f"') + escape)^0 * '"') + local char = token('char',"'" * ((1 - S"\\\r\n\f'") + escape) * "'") + + -- comments + local singleline_comment = P '//' * (1 - S '\r\n\f') ^ 0 + local multiline_comment = '/*' * (1 - P'*/')^0 * '*/' + local comment = token('comment', multiline_comment + singleline_comment) + local prepro = token('prepro',P '#' * (1 - S '\r\n\f') ^ 0) + + -- whitespace + local whitespace = token('space', S('\r\n\f\t ')^1) + + -- ordered choice of all tokens and last-resort error which consumes one character + local any_token = whitespace + number + keyword + ident + + string + char + comment + prepro + operator + token('error', 1) + + + table_of_tokens = Ct(any_token ^ 0) +end + +-- increment [line] by the number of line-ends in [text] +local function sync(line, text) + local index, limit = 1, #text + while index <= limit do + local start, stop = text:find('\r\n', index, true) + if not start then + start, stop = text:find('[\r\n\f]', index) + if not start then break end + end + index = stop + 1 + line = line + 1 + end + return line +end +clexer.sync = sync + +clexer.line = 0 + +-- we only need to synchronize the line-counter for these token types +local multiline_tokens = { comment = true, space = true } +clexer.multiline_tokens = multiline_tokens + +function clexer.scan_c_tokenlist(input) + if not table_of_tokens then + clexer.init() + end + assert(type(input) == 'string', 'bad argument #1 (expected string)') + local line = 1 + local tokens = lpeg.match(table_of_tokens, input) + for i, token in pairs(tokens) do + local t = token[1] + if t == 'operator' or t == 'error' then + token[1] = token[2] + end + token[3] = line + if multiline_tokens[t] then + line = sync(line, token[2]) + end + end + return tokens +end + +--- get a token iterator from a source containing Lua code. +-- S is the source - can be a string or a file-like object (i.e. read() returns line) +-- Note that this token iterator includes spaces and comments, and does not convert +-- string and number tokens - so e.g. a string token is quoted and a number token is +-- an unconverted string. +function clexer.scan_c(input,name) + if type(input) ~= 'string' and input.read then + input = input:read('*a') + end + local tokens = clexer.scan_c_tokenlist(input) + local i, n = 1, #tokens + return function(k) + if k ~= nil then + k = i + k + if k < 1 or k > n then return nil end + return tokens[k] + end + local tok = tokens[i] + i = i + 1 + if tok then + clexer.line = tok[3] + clexer.name = name + return tok[1],tok[2] + end + end + +end + +return clexer diff --git a/Tools/LuaMacro/macro/do.lua b/Tools/LuaMacro/macro/do.lua new file mode 100644 index 0000000..45cf84c --- /dev/null +++ b/Tools/LuaMacro/macro/do.lua @@ -0,0 +1,75 @@ +--- An intelligent 'loop-unrolling' macro. +-- `do_` defines a named scoped macro `var` which is the loop iterator. +-- +-- For example, +-- +-- y = 0 +-- do_(i,1,10 +-- y = y + i +-- ) +-- assert(y == 55) +-- +-- `tuple` is an example of how the expansion of a macro can be +-- controlled by its context. Normally a tuple `A` expands to +-- `A_1,A_2,A_3` but inside `do_` it works element-wise: +-- +-- tuple(3) A,B +-- def_ do3(stmt) do_(k,1,3,stmt) +-- do3(A = B/2) +-- +-- This expands as +-- +-- A_1 = B_1/2 +-- A_2 = B_2/2 +-- A_3 = B_3/2 +-- +-- @module macro.do +local M = require 'macro' + +--- Expand a loop inline. +-- @p var the loop variable +-- @p start initial value of `var` +-- @p finish final value of `var` +-- @p stat the statement containing `var` +-- @macro do_ +M.define('do_(v,s,f,stat)',function(var,start,finish,statements) + -- macros with specified formal args have to make their own putter, + -- and convert the actual arguments to the type they expect. + local put = M.Putter() + var,start,finish = var:get_iden(),start:get_number(),finish:get_number() + M.push_macro_stack('do_',var) + -- 'do_' works by setting the variable macro for each value + for i = start, finish do + put:name 'set_':name(var):number(i):space() + put:tokens(statements) + end + put:name 'undef_':name(var) + put:name '_DROP_':string 'do_':space() + return put +end) + +--- an example of conditional expansion. +-- `tuple` takes a list of variable names, like a declaration list except that it +-- must end with a line end. +-- @macro tuple +M.define('tuple',function(get) + get:expecting '(' + local N = get:number() + get:expecting ')' + local names = get:names '\n' + for _,name in ipairs(names) do + M.define(name,function(get,put) + local loop_var = M.value_of_macro_stack 'do_' + if loop_var then + local loop_idx = tonumber(M.get_macro_value(loop_var)) + return put:name (name..'_'..loop_idx) + else + local out = {} + for i = 1,N do + out[i] = name..'_'..i + end + return put:names(out) + end + end) + end +end) diff --git a/Tools/LuaMacro/macro/forall.lua b/Tools/LuaMacro/macro/forall.lua new file mode 100644 index 0000000..8ec5c68 --- /dev/null +++ b/Tools/LuaMacro/macro/forall.lua @@ -0,0 +1,70 @@ +-------------------- +-- `forall` statement. +-- The syntax is `forall VAR SELECT [if CONDN] do` where +-- `SELECT` is either `in TBL` or `= START,FINISH` +-- +-- For example, +-- +-- forall name in {'one','two'} do print(name) end +-- +-- forall obj in get_objects() if obj:alive() then +-- obj:action() +-- end +-- +-- Using `forall`, we also define _list comprehensions_ like +-- `L{s:upper() | s in names if s:match '%S+'}` +-- +-- @module macro.forall + +local M = require 'macro' + +--- extended for statement. +-- @macro forall +M.define('forall',function(get,put) + local var = get:iden() + local t,v = get:next() + local rest,endt = get:list(M.upto_keywords('do','if')) + put:keyword 'for' + if v == 'in' then + put:iden '_' ',' :iden(var):keyword 'in' + put:iden 'ipairs' '(' :list(rest) ')' + elseif v == '=' then + put:iden(var) '=' :list(rest) + else + M.error("expecting in or =") + end + put:keyword 'do' + if endt[2] == 'if' then + rest,endt = get:list(M.upto_keywords('do')) + put:keyword 'if':list(rest):keyword 'then':iden '_END_END_' + end + return put +end) + +--- list comprehension. +-- Syntax is `L{expr | select}` where `select` is as in `forall`, +-- or `L{expr for select}` where `select` is as in the regular `for` statement. +-- @macro L +-- @return a list of values +-- @usage L{2*x | x in {1,2,3}} == {1,4,9} +-- @usage L{2*x|x = 1,3} == {1,4,9} +-- @usage L{{k,v} for k,v in pairs(t)} +-- @see forall +M.define('L',function(get,put) + local t,v = get:next() -- must be '{' + local expr,endt = get:list(function(t,v) + return t == '|' or t == 'keyword' and v == 'for' + end,'') + local select = get:list('}','') + put '(' : keyword 'function' '(' ')' :keyword 'local':iden 'res' '=' '{' '}' + if endt[2] == '|' then + put:iden'forall' + else + put:keyword 'for' + end + put:list(select):space():keyword'do' + put:iden'res' '[' '#' :iden'res' '+' :number(1) ']' '=' :list(expr):space() + put:keyword 'end' :keyword 'return' : iden 'res' :keyword 'end' ')' '(' ')' + put:iden '_POP_':string'L' + return put +end) diff --git a/Tools/LuaMacro/macro/ifelse.lua b/Tools/LuaMacro/macro/ifelse.lua new file mode 100644 index 0000000..3d5a0df --- /dev/null +++ b/Tools/LuaMacro/macro/ifelse.lua @@ -0,0 +1,90 @@ +local M = require 'macro' + +local function eval (expr,was_expr) + expr = tostring(expr) + if was_expr then expr = "return "..expr end + local chunk = M.assert(loadstring(expr)) + local ok, res = pcall(chunk) + if not ok then M.error("error evaluating "..res) end + return res +end + +local function eval_line (get,was_expr) + local args = get:line() + return eval(args,was_expr) +end + +local function grab (get) + local ilevel = 0 + while true do + local t,v = get() + while t ~= '@' do t = get() end + t,v = get() + if v == 'if' then + ilevel = ilevel + 1 + else -- 'end','elseif','else' + if ilevel > 0 and v == 'end' then + ilevel = ilevel - 1 + elseif ilevel == 0 then return '@'..v end + end + end +end + +M.define('@',function(get,put) + local t,v = get() +--~ print('got',t,v) + return put:iden(v..'_') +end) + +local ifstack,push,pop = {},table.insert,table.remove + +local function push_if (res) +--~ print 'push' + push(ifstack, not (res==false or res==nil)) +end + +local function pop_if () +--~ print 'pop' + pop(ifstack) +end + +M.define('if_',function(get) + local res = eval_line(get,true) + push_if(res) + if not res then + return grab(get) + end +end) + +M.define('elseif_',function(get) + local res + if ifstack[#ifstack] then + res = false + else + res = eval_line(get,true) + pop_if() + push_if(res) + end + if not res then + return grab(get) + end +end) + +M.define('else_',function(get) + if #ifstack == 0 then M.error("mismatched else") end + if ifstack[#ifstack] then + return grab(get) + end +end) + +M.define('end_',function(get) + pop_if() +end) + +M.define('let_',function(get) + eval_line(get) +end) + +M.define('eval_(X)',function(X) + return tostring(eval(X,true)) +end) diff --git a/Tools/LuaMacro/macro/lambda.lua b/Tools/LuaMacro/macro/lambda.lua new file mode 100644 index 0000000..677f997 --- /dev/null +++ b/Tools/LuaMacro/macro/lambda.lua @@ -0,0 +1,22 @@ +--- Short anonymous functions (lambdas). +-- This syntax is suited +-- to any naive token-processor because the payload is always inside parens. +-- It is an example of a macro associated with a 'operator' character. +-- +-- Syntax is `\<args>(<expr>)` +-- +-- `\x(x+10)` is short for +-- `function(x) return x+10 end`. There may be a number of formal argumets, +-- e.g. `\x,y(x+y)` or there may be none, e.g. `\(somefun())`. Such functions +-- may return multiple values, e.g `\x(x+1,x-1)`. +-- +-- @module macro.lambda + +local M = require 'macro' + +M.define ('\\',function(get,put) + local args, body = get:idens('('), get:list() + return put:keyword 'function' '(' : idens(args) ')' : + keyword 'return' : list(body) : space() : keyword 'end' +end) + diff --git a/Tools/LuaMacro/macro/lc.lua b/Tools/LuaMacro/macro/lc.lua new file mode 100644 index 0000000..0d2968d --- /dev/null +++ b/Tools/LuaMacro/macro/lc.lua @@ -0,0 +1,343 @@ +-- Simplifying writing C extensions for Lua +-- Adds new module and class constructs; +-- see class1.lc and str.lc for examples. +local M = require 'macro' + +function dollar_subst(s,tbl) + return (s:gsub('%$%((%a+)%)',tbl)) +end + +-- reuse some machinery from the C-skin experiments +local push,pop = table.insert,table.remove +local bstack,btop = {},{} + +local function push_brace_stack (newv) + newv = newv or {} + newv.lev = 0 + push(bstack,btop) + btop = newv +end + +M.define('{',function() + if btop.lev then + btop.lev = btop.lev + 1 + end + return nil,true --> pass-through macro +end) + +M.define('}',function(get,put) + if not btop.lev then + return nil,true + elseif btop.lev == 0 then + local res + if btop.handler then res = btop.handler(get,put) end + if not res then res = put:space() '}' end + btop = pop(bstack) + return res + else + btop.lev = btop.lev - 1 + return nil,true --> pass-through macro + end +end) + +--------- actual implementation begins ------- + +local append = table.insert +local module + +local function register_functions (names,cnames) + local out = {} + for i = 1,#names do + append(out,(' {"%s",l_%s},'):format(names[i],cnames[i])) + end + return table.concat(out,'\n') +end + +local function finalizers (names) + local out = {} + for i = 1,#names do + append(out,names[i].."(L);") + end + return table.concat(out,'\n') +end + +local typedefs + +local preamble = [[ +#include <lua.h> +#include <lauxlib.h> +#include <lualib.h> +#ifdef WIN32 +#define EXPORT __declspec(dllexport) +#else +#define EXPORT +#endif +#if LUA_VERSION_NUM > 501 +#define lua_objlen lua_rawlen +#endif +]] + +local finis = [[ +static const luaL_Reg $(cname)_funs[] = { + $(funs) + {NULL,NULL} +}; + +EXPORT int luaopen_$(cname) (lua_State *L) { +#if LUA_VERSION_NUM > 501 + lua_newtable(L); + luaL_setfuncs (L,$(cname)_funs,0); + lua_pushvalue(L,-1); + lua_setglobal(L,"$(cname)"); +#else + luaL_register(L,"$(cname)",$(cname)_funs); +#endif + $(finalizers) + return 1; +} +]] + +M.define('module',function(get) + local name = get:string() + local cname = name:gsub('%.','_') + get:expecting '{' + local out = preamble .. typedefs + push_brace_stack{ + name = name, cname = cname, + names = {}, cnames = {}, finalizers = {}, + handler = function() + local out = {} + local funs = register_functions(btop.names,btop.cnames) + local final = finalizers(btop.finalizers) + append(out,dollar_subst(finis, { + cname = cname, + name = name, + funs = funs, + finalizers = final + })) + return table.concat(out,'\n') + end } + module = btop + return out +end) + + +M.define('def',function(get) + local fname = get:name() + local cname = (btop.ns and btop.ns..'_' or '')..fname + append(btop.names,fname) + append(btop.cnames,cname) + get:expecting '(' + local args = get:list():strip_spaces() + get:expecting '{' + local t,space = get() + indent = space:gsub('^%s*[\n\r]',''):gsub('%s$','') + local out = {"static int l_"..cname.."(lua_State *L) {"} + if btop.massage_arg then + btop.massage_arg(args) + end + for i,arg in ipairs(args) do + local mac = arg[1][2]..'_init' + if arg[3] and arg[3][1] == '=' then + mac = mac .. 'o' + i = i .. ',' .. arg[4][2] + end + if not arg[2] then M.error("parameter must be TYPE NAME [= VALUE]") end + append(out,indent..mac..'('..arg[2][2]..','..i..');') + end + --append(out,space) + return table.concat(out,'\n')..space +end) + +M.define('constants',function(get,put) + get:expecting '{' + local consts = get:list '}' :strip_spaces() + --for k,v in pairs(btop) do io.stderr:write(k,'=',tostring(v),'\n') end + -- os.exit() + local fname = 'set_'..btop.cname..'_constants' + local out = { 'static void '..fname..'(lua_State *L) {'} + if not btop.finalizers then M.error("not inside a module") end + append(btop.finalizers,fname) + for _,c in ipairs(consts) do + local type,value,name + if #c == 1 then -- a simple int constant: CONST + name = c:pick(1) + type = 'Int' + value = name + else -- Type CONST [ = VALUE ] + type = c:pick(1) + name = c:pick(2) + if #c == 2 then + value = name + else + value = c:pick(4) + end + end + append(out,('%s_set("%s",%s);'):format(type,name,value )) + end + append(out,'}') + return table.concat(out,'\n') +end) + +M.define('assign',function(get) + get:expecting '{' + local asses = get:list '}' :strip_spaces() + local out = {} + for _,c in ipairs(asses) do + append(out,('%s_set("%s",%s);\n'):format(c:pick(1),c:pick(2),c:pick(4)) ) + end + return table.concat(out,'\n') +end) + +local load_lua = [[ +static void load_lua_code (lua_State *L) { + luaL_dostring(L,lua_code_block); +} +]] + +M.define('lua',function(get) + get:expecting '{' + local block = tostring(get:upto '}') + local code_name = 'lua_code_block' + local out = {'static const char *'.. code_name .. ' = ""\\'} + for line in block:gmatch('([^\r\n]+)') do + line = line:gsub('\\','\\\\'):gsub('"','\\"') + append(out,' "'..line..'\\n"\\') + end + append(out,';') + append(out,load_lua) + out = table.concat(out,'\n') + append(module.finalizers,'load_lua_code') + return out +end) + +typedefs = [[ +typedef const char *Str; +typedef const char *StrNil; +typedef int Int; +typedef double Number; +typedef int Boolean; +]] + + +M.define 'Str_init(var,idx) const char *var = luaL_checklstring(L,idx,NULL)' +M.define 'Str_inito(var,idx,val) const char *var = luaL_optlstring(L,idx,val,NULL)' +M.define 'Str_set(name,value) lua_pushstring(L,value); lua_setfield(L,-2,name)' +M.define 'Str_get(var,name) lua_getfield(L,-1,name); var=lua_tostring(L,-1); lua_pop(L,1)' +M.define 'Str_geti(var,idx) lua_rawgeti(L,-1,idx); var=lua_tostring(L,-1); lua_pop(L,1)' + +M.define 'StrNil_init(var,idx) const char *var = lua_tostring(L,idx)' + +M.define 'Int_init(var,idx) int var = luaL_checkinteger(L,idx)' +M.define 'Int_inito(var,idx,val) int var = luaL_optinteger(L,idx,val)' +M.define 'Int_set(name,value) lua_pushinteger(L,value); lua_setfield(L,-2,name)' +M.define 'Int_get(var,name) lua_getfield(L,-1,name); var=lua_tointeger(L,-1); lua_pop(L,1)' +M.define 'Int_geti(var,idx) lua_rawgeti(L,-1,idx); var=lua_tointeger(L,-1); lua_pop(L,1)' + +M.define 'Number_init(var,idx) double var = luaL_checknumber(L,idx)' +M.define 'Number_inito(var,idx,val) double var = luaL_optnumber(L,idx,val)' +M.define 'NUmber_set(name,value) lua_pushnumber(L,value); lua_setfield(L,-2,name)' +M.define 'Number_get(var,name) lua_getfield(L,-1,name); var=lua_tonumber(L,-1); lua_pop(L,1)' +M.define 'Number_geti(var,idx) lua_rawgeti(L,-1,idx); var=lua_tonumber(L,-1); lua_pop(L,1)' + +M.define 'Boolean_init(var,idx) int var = lua_toboolean(L,idx)' +M.define 'Boolean_set(name,value) lua_pushboolean(L,value); lua_setfield(L,-2,name)' +M.define 'Boolean_get(var,name) lua_getfield(L,-1,name); var=lua_toboolean(L,-1); lua_pop(L,1)' +M.define 'Boolean_geti(var,idx) lua_rawgeti(L,-1,idx); var=lua_toboolean(L,-1); lua_pop(L,1)' + +M.define 'Value_init(var,idx) int var = idx' + +M.define('lua_tests',function(get) + get:expecting '{' + local body = get:upto '}' + local f = io.open(M.filename..'.lua','w') + f:write(tostring(body)) + f:close() +end) + +------ class support ---------------------- + +local klass_ctor = "static void $(klass)_ctor(lua_State *L, $(klass) *this, $(fargs))" + +local begin_klass = [[ + +typedef struct { + $(fields) +} $(klass); + +define_ $(klass)_init(var,idx) $(klass) *var = $(klass)_arg(L,idx) + +#define $(klass)_MT "$(klass)" + +$(klass) * $(klass)_arg(lua_State *L,int idx) { + $(klass) *this = ($(klass) *)luaL_checkudata(L,idx,$(klass)_MT); + luaL_argcheck(L, this != NULL, idx, "$(klass) expected"); + return this; +} + +$(ctor); + +static int push_new_$(klass)(lua_State *L,$(fargs)) { + $(klass) *this = ($(klass) *)lua_newuserdata(L,sizeof($(klass))); + luaL_getmetatable(L,$(klass)_MT); + lua_setmetatable(L,-2); + $(klass)_ctor(L,this,$(aargs)); + return 1; +} + +]] + +local end_klass = [[ + +static const struct luaL_Reg $(klass)_methods [] = { + $(methods) + {NULL, NULL} /* sentinel */ +}; + +static void $(klass)_register (lua_State *L) { + luaL_newmetatable(L,$(klass)_MT); +#if LUA_VERSION_NUM > 501 + luaL_setfuncs(L,$(klass)_methods,0); +#else + luaL_register(L,NULL,$(klass)_methods); +#endif + lua_pushvalue(L,-1); + lua_setfield(L,-2,"__index"); + lua_pop(L,1); +} +]] + +M.define('class',function(get) + local name = get:iden() + get:expecting '{' + local fields = get:upto (function(t,v) + return t == 'iden' and v == 'constructor' + end) + fields = tostring(fields):gsub('%s+$','\n') + get:expecting '(' + local out = {} + local args = get:list() + local f_args = args:strip_spaces() + local a_args = f_args:pick(2) + f_args = table.concat(args:__tostring(),',') + a_args = table.concat(a_args,',') + local subst = {klass=name,fields=fields,fargs=f_args,aargs=a_args } + local proto = dollar_subst(klass_ctor,subst) + subst.ctor = proto + append(out,dollar_subst(begin_klass,subst)) + append(out,proto) + local pp = {{'iden',name},{'iden','this'}} + push_brace_stack{ + names = {}, cnames = {}, ns = name, cname = name, + massage_arg = function(args) + table.insert(args,1,pp) + end, + handler = function(get,put) + append(module.finalizers,name.."_register") + local methods = register_functions(btop.names,btop.cnames) + return dollar_subst(end_klass,{methods=methods,klass=name,fargs=f_args,aargs=a_args}) + end + } + return table.concat(out,'\n') +end) + diff --git a/Tools/LuaMacro/macro/lexer.lua b/Tools/LuaMacro/macro/lexer.lua new file mode 100644 index 0000000..58ab53a --- /dev/null +++ b/Tools/LuaMacro/macro/lexer.lua @@ -0,0 +1,179 @@ +--[[--- A Lua lexical scanner using LPeg. += CREDITS +Written by Peter Odding, 2007/04/04 + += THANKS TO +- the Lua authors for a wonderful language; +- Roberto for LPeg; +- caffeine for keeping me awake :) + += LICENSE +Shamelessly ripped from the SQLite[3] project: + + The author disclaims copyright to this source code. In place of a legal + notice, here is a blessing: + + May you do good and not evil. + May you find forgiveness for yourself and forgive others. + May you share freely, never taking more than you give. + +@module macro.lexer +--]] + +local lexer = {} +local lpeg = require 'lpeg' +local P, R, S, C, Cb, Cc, Cg, Cmt, Ct = + lpeg.P, lpeg.R, lpeg.S, lpeg.C, lpeg.Cb, lpeg.Cc, lpeg.Cg, lpeg.Cmt, lpeg.Ct + +-- create a pattern which captures the lua value [id] and the input matching +-- [patt] in a table +local function token(id, patt) return Ct(Cc(id) * C(patt)) end + +-- private interface +local table_of_tokens +local extra_tokens + +function lexer.add_extra_tokens(extra) + extra_tokens = extra_tokens or {} + for _,t in ipairs(extra) do + table.insert(extra_tokens,t) + end + table_of_tokens = nil -- re-initialize +end + +function lexer.init () + local digit = R('09') + + -- range of valid characters after first character of identifier + --local idsafe = R('AZ', 'az', '\127\255') + P '_' + local idsafe = R('AZ', 'az') + P '_' + R '\206\223' * R '\128\255' + -- operators + local OT = P '==' + if extra_tokens then + for _,ex in ipairs(extra_tokens) do + OT = OT + P(ex) + end + end + local operator = token('operator', OT + P '.' + P '~=' + P '<=' + P '>=' + P '...' + + P '..' + S '+-*/%^#=<>;:,.{}[]()') + -- identifiers + local ident = token('iden', idsafe * (idsafe + digit) ^ 0) + + -- keywords + local keyword = token('keyword', (P 'and' + P 'break' + P 'do' + P 'elseif' + + P 'else' + P 'end' + P 'false' + P 'for' + P 'function' + P 'if' + + P 'in' + P 'local' + P 'nil' + P 'not' + P 'or' + P 'repeat' + P 'return' + + P 'then' + P 'true' + P 'until' + P 'while') * -(idsafe + digit)) + + -- numbers + local number_sign = S'+-'^-1 + local number_decimal = digit ^ 1 + local number_hexadecimal = P '0' * S 'xX' * R('09', 'AF', 'af') ^ 1 + local number_float = (digit^1 * P'.' * digit^0 + P'.' * digit^1) * + (S'eE' * number_sign * digit^1)^-1 + local number = token('number', number_hexadecimal + + number_float + + number_decimal) + + -- callback for [=[ long strings ]=] + -- ps. LPeg is for Lua what regex is for Perl, which makes me smile :) + local equals = P '=' ^ 0 + local open = P '[' * Cg(equals, "init") * P '[' * P '\n' ^ -1 + local close = P ']' * C(equals) * P ']' + local closeeq = Cmt(close * Cb "init", function (s, i, a, b) return a == b end) + local longstring = open * C((P(1) - closeeq)^0) * close --/ 1 + + -- strings + local singlequoted_string = P "'" * ((1 - S "'\r\n\f\\") + (P '\\' * 1)) ^ 0 * "'" + local doublequoted_string = P '"' * ((1 - S '"\r\n\f\\') + (P '\\' * 1)) ^ 0 * '"' + local string = token('string', singlequoted_string + + doublequoted_string + + longstring) + + -- comments + local singleline_comment = P '--' * (1 - S '\r\n\f') ^ 0 + local multiline_comment = P '--' * longstring + local comment = token('comment', multiline_comment + singleline_comment) + + -- whitespace + local whitespace = token('space', S('\r\n\f\t ')^1) + + -- ordered choice of all tokens and last-resort error which consumes one character + local any_token = whitespace + number + keyword + ident + + string + comment + operator + token('error', 1) + + + table_of_tokens = Ct(any_token ^ 0) +end + +-- increment [line] by the number of line-ends in [text] +local function sync(line, text) + local index, limit = 1, #text + while index <= limit do + local start, stop = text:find('\r\n', index, true) + if not start then + start, stop = text:find('[\r\n\f]', index) + if not start then break end + end + index = stop + 1 + line = line + 1 + end + return line +end +lexer.sync = sync + +lexer.line = 0 + +-- we only need to synchronize the line-counter for these token types +local multiline_tokens = { comment = true, string = true, space = true } +lexer.multiline_tokens = multiline_tokens + +function lexer.scan_lua_tokenlist(input) + if not table_of_tokens then + lexer.init() + end + assert(type(input) == 'string', 'bad argument #1 (expected string)') + local line = 1 + local tokens = lpeg.match(table_of_tokens, input) + for i, token in pairs(tokens) do + local t = token[1] + if t == 'operator' or t == 'error' then + token[1] = token[2] + end + token[3] = line + if multiline_tokens[t] then + line = sync(line, token[2]) + end + end + return tokens +end + +--- get a token iterator from a source containing Lua code. +-- Note that this token iterator includes spaces and comments, and does not convert +-- string and number tokens - so e.g. a string token is quoted and a number token is +-- an unconverted string. +-- @param input the source - can be a string or a file-like object (i.e. read() returns line) +-- @param name for the source +function lexer.scan_lua(input,name) + if type(input) ~= 'string' and input.read then + input = input:read('*a') + end + local tokens = lexer.scan_lua_tokenlist(input) + local i, n = 1, #tokens + return function(k) + if k ~= nil then + k = i + k + if k < 1 or k > n then return nil end + return tokens[k] + end + local tok = tokens[i] + i = i + 1 + if tok then + lexer.line = tok[3] + lexer.name = name + return tok[1],tok[2] + end + end +end + +return lexer diff --git a/Tools/LuaMacro/macro/lib/class.lua b/Tools/LuaMacro/macro/lib/class.lua new file mode 100644 index 0000000..f762f36 --- /dev/null +++ b/Tools/LuaMacro/macro/lib/class.lua @@ -0,0 +1,35 @@ +---- +-- a basic class mechanism. +-- Used for some of the demonstrations; the `class` macro in the `module` +-- package uses it. It provides a single function which returns a new 'class'. +-- The resulting object can be called to generate an instance of the class. +-- You may provide a base class for single inheritance; in this case, the functions +-- of the base class will be copied into the new class' metatable (so-called 'fat metatable') +-- +-- Example: +-- +-- local class = require 'macro.lib.class' +-- A = class() +-- function A._init(name) self.name = name end +-- a = A("hello") +-- assert(a.name == "hello") +-- +-- @module macro.lib.class + +return function (base) + -- OOP with single inheritance + local klass,cmt = {},{} + if base then -- 'fat metatable' inheritance + for k,v in pairs(base) do klass[k] = v end + end + klass.__index = klass + -- provide a callable constructor that invokes user-supplied ctor + function cmt:__call(...) + local obj = setmetatable({},klass) + if klass._init then klass._init(obj,...) + elseif base and base._init then base._init(base,...) end + return obj + end + setmetatable(klass,cmt) + return klass +end diff --git a/Tools/LuaMacro/macro/lib/test.lua b/Tools/LuaMacro/macro/lib/test.lua new file mode 100644 index 0000000..5fff39e --- /dev/null +++ b/Tools/LuaMacro/macro/lib/test.lua @@ -0,0 +1,144 @@ +--- `assert_` macro library support. +-- This module may of course be used on its own; `assert_` merely provides +-- some syntactical sugar for its functionality. It is based on Penlight's +-- `pl.test` module. +-- @module macro.libs.test + +local test = {} + +local _eq,_tostring + +-- very much like tablex.deepcompare from Penlight +function _eq (v1,v2) + if type(v1) ~= type(v2) then return false end + -- if the value isn't a table, or it has defined the equality operator.. + local mt = getmetatable(v1) + if (mt and mt.__eq) or type(v1) ~= 'table' then + return v1 == v2 + end + -- both values are plain tables + if v1 == v2 then return true end -- they were the same table... + for k1,x1 in pairs(v1) do + local x2 = v2[k1] + if x2 == nil or not _eq(x1,x2) then return false end + end + for k2,x2 in pairs(v2) do + local x1 = v1[k2] + if x1 == nil or not _eq(x1,x2) then return false end + end + return true +end + +local function keyv (k) + if type(k) ~= 'string' then + k = '['..k..']' + end + return k +end + +function _tostring (val) + local mt = getmetatable(val) + if (mt and mt.__tostring) or type(val) ~= 'table' then + if type(val) == 'string' then + return '"'..tostring(val)..'"' + else + return tostring(val) + end + end + -- dump the table; doesn't need to be pretty! + local res = {} + local function put(s) res[#res+1] = s end + put '{' + for k,v in pairs(val) do + put(keyv(k)..'=') + put(_tostring(v)) + put ',' + end + table.remove(res) -- remove last ',' + put '}' + return table.concat(res) +end + +local function _lt (v1,v2) return v1 < v2 end +local function _gt (v1,v2) return v1 > v2 end +local function _match (v1,v2) return v1:match(v2) end + +local function _assert (v1,v2,cmp,msg) + if not cmp(v1,v2) then + print('first:',_tostring(v1)) + print(msg) + print('second:',_tostring(v2)) + error('assertion failed',3) + end +end + +--- assert if parameters are not equal. If the values are tables, +-- they will be compared by value. +-- @param v1 given value +-- @param v2 test value +function test.assert_eq (v1,v2) + _assert(v1,v2,_eq,"is not equal to"); +end + +--- assert if first parameter is not less than second. +-- @param v1 given value +-- @param v2 test value +function test.assert_lt (v1,v2) + _assert(v1,v2,_lt,"is not less than") +end + +--- assert if first parameter is not greater than second. +-- @param v1 given value +-- @param v2 test value +function test.assert_gt (v1,v2) + _assert(v1,v2,_gt,"is not greater than") +end + +--- assert if first parameter string does not match the second. +-- The condition is `v1:match(v2)`. +-- @param v1 given value +-- @param v2 test value +function test.assert_match (v1,v2) + _assert(v1,v2,_match,"does not match") +end + +-- return the error message from a function that raises an error. +-- Will raise an error if the function did not raise an error. +-- @param fun the function +-- @param ... any arguments to the function +-- @return the error message +function test.pcall_no(fun,...) + local ok,err = pcall(fun,...) + if ok then error('expression did not throw error',3) end + return err +end + +local tuple = {} + +function tuple.__eq (a,b) + if a.n ~= b.n then return false end + for i=1, a.n do + if not _eq(a[i],b[i]) then return false end + end + return true +end + +function tuple.__tostring (self) + local ts = {} + for i = 1,self.n do + ts[i] = _tostring(self[i]) + end + return '('..table.concat(ts,',')..')' +end + +--- create a tuple capturing multiple return values. +-- Equality between tuples means that all of their values are equal; +-- values may be `nil` +-- @param ... any values +-- @return a tuple object +function test.tuple(...) + return setmetatable({n=select('#',...),...},tuple) +end + +return test + diff --git a/Tools/LuaMacro/macro/module.lua b/Tools/LuaMacro/macro/module.lua new file mode 100644 index 0000000..a8e1b8d --- /dev/null +++ b/Tools/LuaMacro/macro/module.lua @@ -0,0 +1,132 @@ +--[[--- +Easy no-fuss modules. + +Any function inside the module will be exported, unless it is explicitly +local. The functions are declared up front using patching, leading to efficient +calls between module functions. + + require_ 'module' + + function one () + return two() + end + + function two () + return 42 + end + +Classes can also be declared inside modules: + + require_ 'module' + + class A + function set(self,val) @val = val end + function get(self) return @val end + end + +Within class definitions, the macro `@` expands to either `self.` or `self:` depending +on context, and provides a Ruby-like shortcut. + +If you give these modules names with `m.lua` extension like `mod.m.lua`, then you can +simply use `require()` to use them with LuaMacro. + +@module macro.module +]] +local M = require 'macro' + +local locals, locals_with_value = {}, {} +local ref + +local function module_add_new_local (name) + locals[#locals+1] = name +end + +local function module_add_new_local_with_value (name,value) + locals_with_value[name] = value +end + + +local function was_local_function (get) + local tl,keyw = get:peek(-1) + return tl=='keyword' and keyw=='local' +end + +-- exclude explicitly local functions and anonymous functions. +M.keyword_handler('function',function(get) + local tn,name = get:peek(1) + local was_local = was_local_function(get) + if not was_local and tn == 'iden' then + module_add_new_local(name) + end +end) + +-- when the module is closed, this will patch the locals and +-- output the module table. +M.keyword_handler('END',function(get) + local concat = table.concat + local patch = '' + if next(locals_with_value) then + local lnames,lvalues = {},{} + local i = 1 + for k,v in pairs(locals_with_value) do + lnames[i] = k + lvalues[i] = v + i = i + 1 + end + patch = patch..'local '..concat(lnames,',')..'='..concat(lvalues,',')..'; ' + end + if #locals > 0 then + patch = patch .. 'local '..concat(locals,',') + end + get:patch(ref,patch) + local dcl = {} + for i,name in ipairs(locals) do + dcl[i] = name..'='..name + end + dcl = table.concat(dcl,', ') + return 'return {' .. dcl .. '}' +end) + +local no_class_require + +-- the meaning of @f is either 'self.f' for fields, or 'self:f' for methods. +local function at_handler (get,put) + local tn,name,tp = get:peek2(1) + M.assert(tn == 'iden','identifier must follow @') + return put:iden ('self',true) (tp=='(' and ':' or '.') +end + +local function method_handler (get,put) + local tn,name,tp = get:peek2() + if not was_local_function(get) and tn == 'iden' and tp == '(' then + return put ' ' :iden ('_C',true) '.' + end +end + +M.define ('_C_',function() + M.define_scoped('@',at_handler) + if not no_class_require then + module_add_new_local_with_value('_class','require "macro.lib.class"') + no_class_require = true + end + M.scoped_keyword_handler('function',method_handler) +end) + +M.define('class',function(get) + local base = '' + local name = get:iden() + if get:peek(1) == ':' then + get:next() + base = get:iden() + end + module_add_new_local(name) + return ('do local _C = _class(%s); %s = _C; _C_\n'):format(base,name) +end) + +-- the result of the macro is just a placeholder for the locals +return function(get,put) + ref = get:placeholder(put) + return put +end + + diff --git a/Tools/LuaMacro/macro/try.lua b/Tools/LuaMacro/macro/try.lua new file mode 100644 index 0000000..8e49eb0 --- /dev/null +++ b/Tools/LuaMacro/macro/try.lua @@ -0,0 +1,47 @@ +--- A try/except block. +-- This generates syntactical sugar around `pcal`l, and correctly +-- distinguishes between the try block finishing naturally and +-- explicitly using 'return' with no value. This is handled by +-- converting any no value `return` to `return nil`. +-- +-- Apart from the usual creation of a closure, this uses a table +-- to capture all the results. Not likely to win speed contests, +-- but intended to be correct. +-- @module macro.try + +local M = require 'macro' + +local function pack (...) + local args = {...} + args.n = select('#',...) + return args +end + +function pcall_(fn,...) + return pack(pcall(fn,...)) +end + +local function check_return_value(get,put) + local t,v = get:next() + put:space() + if t=='keyword' and (v=='end' or v=='else' or v=='until') then + put:keyword 'nil' + end + return put(t,v) +end + + +M.define('RR_',M.make_scoped_handler('return',check_return_value)) + + +--- A try macro, paired with except. +-- +-- try +-- maybe_something_bad() +-- except (e) +-- print(e) +-- end +-- @macro try +M.define 'try do local r_ = pcall_(function() RR_ ' +M.define 'except(e) end); if r_[1] then if r_.n > 1 then return unpack(r_,2,r_.n) end else local e = r_[2] _END_END_ ' + diff --git a/Tools/LuaMacro/macro/with.lua b/Tools/LuaMacro/macro/with.lua new file mode 100644 index 0000000..de51590 --- /dev/null +++ b/Tools/LuaMacro/macro/with.lua @@ -0,0 +1,31 @@ +--[[-- +A `with` statement. This works more like the Visual Basic statement than the +Pascal one; fields have an explicit period to indicate that they are special. +This makes variable scoping explcit. + + aLongTableName = {} + with aLongTableName do + .a = 1 + .b = {{x=1},{x=2}} + .c = {f = 2} + print(.a,.c.f,.b[1].x) + end + +Fields that follow an identifier or a `}` are passed as-is. + +@module macro.with +]] +local M = require 'macro' + +M.define('with',function(get,put) + M.define_scoped('.',function() + local lt,lv = get:peek(-1,true) -- peek before the period... + if lt ~= 'iden' and lt ~= ']' then + return '_var.' + else + return nil,true -- pass through + end + end) + local expr = get:upto 'do' + return 'do local _var = '..tostring(expr)..'; ' +end) diff --git a/Tools/LuaMacro/readme.md b/Tools/LuaMacro/readme.md new file mode 100644 index 0000000..e86bbfb --- /dev/null +++ b/Tools/LuaMacro/readme.md @@ -0,0 +1,1010 @@ +## LuaMacro - a macro preprocessor for Lua + +This is a library and driver script for preprocessing and evaluating Lua code. +Lexical macros can be defined, which may be simple C-preprocessor style macros or +macros that change their expansion depending on the context. + +It is a new, rewritten version of the +[Luaforge](http://luaforge.net/projects/luamacro/) project of the same name, which +required the [token filter +patch](http://www.tecgraf.puc-rio.br/~lhf/ftp/lua/#tokenf) by Luiz Henrique de +Figueiredo. This patch allowed Lua scripts to filter the raw token stream before +the compiler stage. Within the limits imposed by the lexical filter approach this +worked pretty well. However, the token filter patch is unlikely to ever become +part of mainline Lua, either in its original or +[revised](http://lua-users.org/lists/lua-l/2010-02/msg00325.html) form. So the most +portable option becomes precompilation, but Lua bytecode is not designed to be +platform-independent and in any case changes faster than the surface syntax of the +language. So using LuaMacro with LuaJIT would have required re-applying the patch, +and would remain within the ghetto of specialized, experimental use. + +This implementation uses a [LPeg](http://www.inf.puc-rio.br/~roberto/lpeg.html) +lexical analyser originally by [Peter +Odding](http://lua-users.org/wiki/LpegRecipes) to tokenize Lua source, and builds +up a preprocessed string explicitly, which then can be loaded in the usual way. +This is not as efficient as the original, but it can be used by anyone with a Lua +interpreter, whether it is Lua 5.1, 5.2 or LuaJIT 2. An advantage of fully building +the output is that it becomes much easier to debug macros when you can actually see +the generated results. (Another example of a LPeg-based Lua macro preprocessor is +[Luma](http://luaforge.net/projects/luma/)) + +It is not possible to discuss macros in Lua without mentioning Fabien Fleutot's +[Metalua](metalua.luaforge.net/) which is an alternative Lua compiler which +supports syntactical macros that can work on the AST (Abstract Syntax Tree) itself +of Lua. This is clearly a technically superior way to extend Lua syntax, but again +has the disadvantage of being a direct-to-bytecode compiler. (Perhaps it's also a +matter of taste, since I find it easier to think about extending Lua on the lexical +level.) + +My renewed interest in Lua lexical macros came from some discussions on the Lua +mailing list about numerically optimal Lua code using LuaJIT. We have been spoiled +by modern optimizing C/C++ compilers, where hand-optimization is often discouraged, +but LuaJIT is new and requires some assistance. For instance, unrolling short loops +can make a dramatic difference, but Lua does not provide the key concept of +constant value to assist the compiler. So a very straightforward use of a macro +preprocessor is to provide named constants in the old-fashioned C way. Very +efficient code can be generated by generalizing the idea of 'varargs' into a +statically-compiled 'tuple' type. + + tuple(3) A,B + +The assigment `A = B` is expanded as: + + A_1,A_2,A_3 = B_1,B_2,B_3 + +I will show how the expansion can be made context-sensitive, so that the +loop-unrolling macro `do_` changes this behaviour: + + do_(i,1,3, + A = 0.5*B + ) + +expands to: + + A_1 = 0.5*B_1 + A_2 = 0.5*B_2 + A_3 = 0.5*B_3 + +Another use is crafting DSLs, particularly for end-user scripting. For instance, +people may be more comfortable with `forall x in t do` rather than `for _,x in +ipairs(t) do`; there is less to explain in the first form and it translates +directly to the second form. Another example comes from this common pattern: + + some_action(function() + ... + end) + +Using the following macro: + + def_ block (function() _END_CLOSE_ + +we can write: + + some_action block + ... + end + +A criticism of traditional lexical macros is that they don't respect the scoping +rules of the language itself. Bad experiences with the C preprocessor lead many to +regard them as part of the prehistory of computing. The macros described here can +be lexically scoped, and can be as 'hygenic' as necessary, since their expansion +can be finely controlled with Lua itself. + +For me, a more serious charge against 'macro magic' is that it can lead to a +private dialect of the language (the original Bourne shell was written in C +'skinned' to look like Algol 68.) This often indicates a programmer uncomfortable +with a language, who wants it to look like something more familiar. Relying on a +preprocessor may mean that programmers need to immerse themselves more in the idioms of +the new language. + +That being said, macros can extend a language so that it can be more expressive for +a particular task, particularly if the users are not professional programmers. + +### Basic Macro Substitution + +To install LuaMacro, expand the archive and make a script or batch file that points +to `luam.lua`, for instance: + + lua /home/frodo/luamacro/luam.lua $* + +(Or '%*' if on Windows.) Then put this file on your executable path. + +Any Lua code loaded with `luam` goes through four distinct steps: + + * loading and defining macros + * preprocessing + * compilation + * execution + +The last two steps happen within Lua itself, but always occur, even though the Lua +compiler is fast enough that we mostly do not bother to save the generated bytecode. + +For example, consider this `hello.lua`: + + print(HELLO) + +and `hello-def.lua`: + + local macro = require 'macro' + macro.define 'HELLO "Hello, World!"' + +To run the program: + + $> luam -lhello-def hello.lua + Hello, World! + +So the module `hello-def.lua` is first loaded (compiled and executed, but not +preprocessed) and only then `hello.lua` can be preprocessed and then loaded. + +Naturaly, there are easier ways to use LuaMacro, but I want to emphasize the +sequence of macro loading, preprocessing and script loading. `luam` has a `-d` +flag, meaning 'dump', which is very useful when debugging the output of the +preprocessing step: + + $> luam -d -lhello-def hello.lua + print("Hello, World!") + +`hello2.lua` is a more sensible first program: + + require_ 'hello-def' + print(HELLO) + +You cannot use the Lua `require` function at this point, since `require` is only +executed when the program starts executing and we want the macro definitions to be +available during the current compilation. `require_` is the macro version, which +loads the file at compile-time. + +New with 2.5 is the default @ shortcut available when using `luam`, +so `require_` can be written `@require`. +(`@` is itself a macro, so you can redefine it if needed.) + +There is also `include_/@include`, which is analogous to `#include` in `cpp`. It takes a +file path in quotes, and directly inserts the contents of the file into the current +compilation. Although tempting to use, it will not work here because again the +macro definitions will not be available at compile-time. + +`hello3.lua` fits much more into the C preprocessor paradigm, which uses the `def_` +macro: + + @def HELLO "Hello, World!" + print(HELLO) + +(Like `cpp`, such macro definitions end with the line; however, there is no +equivalent of `\` to extend the definition over multiple lines.) + +With 2.1, an alternative syntax `def_ (name body)` is also available, which can be +embedded inside a macro expression: + + def_ OF_ def_ (of elseif _value ==) + +Or even extend over several lines: + + def_ (complain(msg,n) + for i = 1,n do + print msg + end + ) + +`def_` works pretty much like `#define`, for instance, `def_ SQR(x) ((x)*(x))`. A +number of C-style favourites can be defined, like `assert_` using `_STR_`, which is +a predefined macro that 'stringifies' its argument. + + def_ assert_(condn) assert(condn,_STR_(condn)) + +`def_` macros are _lexically scoped_: + + local X = 1 + if something then + def_ X 42 + assert(X == 42) + end + assert(X == 1) + +LuaMacro keeps track of Lua block structure - in particular it knows when a +particular lexical scope has just been closed. This is how the `_END_CLOSE_` +built-in macro works + + def_ block (function() _END_CLOSE_ + + my_fun block + do_something_later() + end + +When the current scope closes with `end`, LuaMacro appends the necessary ')' to +make this syntax valid. + +A common use of macros in both C and Lua is to inline optimized code for a case. +The Lua function `assert()` always evaluates its second argument, which is not +always optimal: + + def_ ASSERT(condn,expr) if condn then else error(expr) end + + ASSERT(2 == 1,"damn! ".. 2 .." is not equal to ".. 1) + +If the message expression is expensive to execute, then this can give better +performance at the price of some extra code. `ASSERT` is now a statement, not a +function, however. + +### Conditional Compilation + +For this to work consistently, you need to use the `@` shortcut: + + @include 'test.inc' + @def A 10 + ... + +This makes macro 'preprocessor' statements stand out more. Conditional compilation +works as you would expect from C: + + -- test-cond.lua + @if A + print 'A defined' + @else + print 'A not defined' + @end + @if os.getenv 'P' + print 'Env P is defined' + @end + +Now, what is `A`? It is a Lua expression which is evaluated at _preprocessor_ +time, and if it returns any value except `nil` or `false` it is true, using +the usual Lua rule. Assuming `A` is just a global variable, how can it be set? + + $ luam test-cond.lua + A not defined + $ luam -VA test-cond.lua + A defined + $ export P=1 + $ luam test-cond.lua + A not defined + Env P is defined + +Although this looks very much like the standard C preprocessor, the implementation +is rather different - `@if` is a special macro which evaluates its argument +(everything on the rest of the line) as a _Lua expression_ +and skips upto `@end` (or `@else` or `@elseif`) if that condition is false. + + +### Using macro.define + +`macro.define` is less convenient than `def_` but much more powerful. The extended +form allows the substitution to be a _function_ which is called in-place at compile +time. These definitions must be loaded before they can be used, +either with `-l` or with `@require`. + + macro.define('DATE',function() + return '"'..os.date('%c')..'"' + end) + +Any text which is returned will be tokenized and inserted into the output stream. +The explicit quoting here is needed to ensure that `DATE` will be replaced by the +string "04/30/11 09:57:53". ('%c' gives you the current locale's version of the +date; for a proper version of this macro, best to use `os.date` [with more explicit +formats](http://www.lua.org/pil/22.1.html) .) + +This function can also return nothing, which allows you to write macro code purely +for its _side-effects_. + +Non-operator characters like `@`,`$`, etc can be used as macros. For example, say +you like shell-like notation `$HOME` for expanding environment variables in your +scripts. + + macro.define '$(x) os.getenv(_STR_(x))' + +A script can now say `$(PATH)` and get the expected expansion, Make-style. But we +can do better and support `$PATH` directly: + + macro.define('$',function(get) + local var = get:iden() + return 'os.getenv("'..var..'")' + end) + +If a macro has no parameters, then the substitution function receives a 'getter' +object. This provides methods for extracting various token types from the input +stream. Here the `$` macro must be immediately followed by an identifier. + +We can do better, and define `$` so that something like `$(pwd)` has the same +meaning as the Unix shell: + + macro.define('$',function(get) + local t,v = get() + if t == 'iden' then + return 'os.getenv("'..v..'")' + elseif t == '(' then + local rest = get:upto ')' + return 'os.execute("'..tostring(rest)..'")' + end + end) + +(The getter `get` is callable, and returns the type and value of the next token.) + +It is probably a silly example, but it illustrates how a macro can be overloaded +based on its lexical context. Much of the expressive power of LuaMacro comes from +allowing macros to fetch their own parameters in this way. It allows us to define +new syntax and go beyond 'pseudo-functions', which is more important for a +conventional-syntax language like Lua, rather than Lisp where everything looks like +a function anyway. These kinds of macros are called 'reader' macros in the Lisp world, +since they temporarily take over reading code. + +It is entirely possible for macros to create macros; that is what `def_` does. +Consider how to add the concept of `const` declarations to Lua: + + const N,M = 10,20 + +Here is one solution: + + macro.define ('const',function(get) + get() -- skip the space + local vars = get:idens '=' + local values = get:list '\n' + for i,name in ipairs(vars) do + macro.assert(values[i],'each constant must be assigned!') + macro.define_scoped(name,tostring(values[i])) + end + end) + +The key to making these constants well-behaved is `define_scoped`, which installs a +block handler which resets the macro to its original value, which is usually `nil`. +This test script shows how the scoping works: + + require_ 'const' + do + const N,M = 10,20 + do + const N = 5 + assert(N == 5) + end + assert(N == 10 and M == 20) + end + assert(N == nil and M == nil) + + +If we were designing a DSL intended for non-technical users, then we cannot just +say to them 'learn the language properly - go read PiL!'. It would be easier to +explain: + + forall x in {10,20,30} do + +than the equivalent generic `for` loop. `forall` can be implemented fairly simply +as a macro: + + macro.define('forall',function(get) + local var = get:iden() + local t,v = get:next() -- will be 'in' + local rest = tostring(get:upto 'do') + return ('for _,%s in ipairs(%s) do'):format(var,rest) + end) + +That is, first get the loop variable, skip `in`, grab everything up to `do` and +output the corresponding `for` statement. + +Useful macros can often be built using these new forms. For instance, here is a +simple list comprehension macro: + + macro.define('L(expr,select) '.. + '(function() local res = {} '.. + ' forall select do res[#res+1] = expr end '.. + 'return res end)()' + ) + +For example, `L(x^2,x in t)` will make a list of the squares of all elements in `t`. + +Why don't we use a long string here? Because we don't wish to insert any extra line +feeds in the output.`macro.forall` defines more sophisticated `forall` statements +and list comprehension expressions, but the principle is the same - see 'tests/test-forall.lua' + +There is a second argument passed to the substitution function, which is a 'putter' +object - an object for building token lists. For example, a useful shortcut for +anonymous functions: + + M.define ('\\',function(get,put) + local args = get:idens('(') + local body = get:list() + return put:keyword 'function' '(' : idens(args) ')' : + keyword 'return' : list(body) : space() : keyword 'end' + end) + +The `put` object has methods for appending particular kinds of tokens, such as +keywords and strings, and is also callable for operator tokens. These always return +the object itself, so the output can be built up with chaining. + +Consider `\x,y(x+y)`: the `idens` getter grabs a comma-separated list of identifier +names upto the given token; the `list` getter grabs a general argument list. It +returns a list of token lists and by default stops at ')'. This 'lambda' notation +was suggested by Luiz Henrique de Figueiredo as something easily parsed by any +token-filtering approach - an alternative notation `|x,y| x+y` has been +[suggested](http://lua-users.org/lists/lua-l/2009-12/msg00071.html) but is +generally impossible to implement using a lexical scanner, since it would have to +parse the function body as an expression. The `\\` macro also has the advantage +that the operator precedence is explicit: in the case of `\\(42,'answer')` it is +immediately clear that this is a function of no arguments which returns two values. + +I would not necessarily suggest that lambdas are a good thing in +production code, but they _can_ be useful in iteractive exploration and within tests. + +Macros with explicit parameters can define a substitution function, but this +function receives the values themselves, not the getter and putter objects. These +values are _token lists_ and must be converted into the expected types using the +token list methods: + + macro.define('test_(var,start,finish)',function(var,start,finish) + var,start,finish = var:get_iden(),start:get_number(),finish:get_number() + print(var,start,finish) + end) + + +Since no `put` object is received, such macros need to construct their own: + + local put = M.Putter() + ... + return put + +(They can of course still just return the substitution as text.) + +### Dynamically controlling macro expansion + +Consider this loop-unrolling macro: + + do_(i,1,3, + y = y + i + ) + +which will expand as + + y = y + 1 + y = y + 2 + y = y + 3 + +For each iteration, it needs to define a local macro `i` which expands to 1,2 and 3. + + macro.define('do_(v,s,f,stat)',function(var,start,finish,statements) + local put = macro.Putter() + var,start,finish = var:get_iden(),start:get_number(),finish:get_number() + macro.push_token_stack('do_',var) + for i = start, finish do + -- output `set_ <var> <value> ` + put:iden 'set_':iden(var):number(i):space() + put:tokens(statements) + end + -- output `undef_ <var> <value>` + put:iden 'undef_':iden(var) + -- output `_POP_ 'do_'` + put:iden '_DROP_':string 'do_' + return put + end) + +Ignoring the macro stack manipulation for a moment, it works by inserting `set_` +macro assignments into the output. That is, the raw output looks like this: + + set_ i 1 + y = y + i + set_ i 2 + y = y + i + set_ i 2 + y = y + i + undef_ i + _DROP_ 'do_' + +It's important here to understand that LuaMacro does not do _recursive_ +substitution. Rather, the output of macros is pushed out to the stream which is +then further substituted, etc. So we do need these little helper macros to set the +loop variable at each point. + +Using the macro stack allows macros to be aware that they are expanding inside a +`do_` macro invocation. Consider `tuple`, which is another macro which creates +macros: + + tuple(3) A,B + A = B + +which would expand as + + local A_1,A_2,A_3,B_1,B_2,B_3 + A_1,A_2,A_3 = B_1,B_2,B_3 + +But we would like + + do_(i,1,3, + A = B/2 + ) + +to expand as + + A_1 = B_1/2 + A_2 = B_2/2 + A_2 = B_2/2 + +And here is the definition: + + macro.define('tuple',function(get) + get:expecting '(' + local N = get:number() + get:expecting ')' + get:expecting 'space' + local names = get:idens '\n' + for _,name in ipairs(names) do + macro.define(name,function(get,put) + local loop_var = macro.value_of_macro_stack 'do_' + if loop_var then + local loop_idx = tonumber(macro.get_macro_value(loop_var)) + return put:iden (name..'_'..loop_idx) + else + local out = {} + for i = 1,N do + out[i] = name..'_'..i + end + return put:idens(out) + end + end) + end + end) + +The first expansion case happens if we are not within a `do_` macro; a simple list +of names is outputted. Otherwise, we know what the loop variable is, and can +directly ask for its value. + +### Operator Macros + +You can of course define `@` to be a macro; a new feature allows you to add new +operator tokens: + + macro.define_tokens {'##','@-'} + +which can then be used with `macro.define`, but also now with `def_`. It's now +possible to define a list comprehension syntax that reads more naturally, e.g. +`{|x^2| i=1,10}` by making `{|` into a new token. + +Up to now, making a Lua operator token such as `.` into a macro was not so useful. +Such a macro may now return an extra value which indicates that the operator should +simply 'pass through' as is. Consider defining a `with` statement: + + with A do + .x = 1 + .y = 2 + end + +I've deliberately indicated the fields using a dot (a rare case of Visual Basic +syntax being superior to Delphi). So it is necessary to overload '.' and look at +the previous token: if it isn't a case like `name.` or `].` then we prepend the +table. Otherwise, the operator must simply _pass through_, to prevent an +uncontrolled recursion. + + M.define('with',function(get,put) + M.define_scoped('.',function() + local lt,lv = get:peek(-1,true) -- peek before the period... + if lt ~= 'iden' and lt ~= ']' then + return '_var.' + else + return nil,true -- pass through + end + end) + local expr = get:upto 'do' + return 'do local _var = '..tostring(expr)..'; ' + end) + +Again, scoping means that this behaviour is completely local to the with-block. + +A more elaborate experiment is `cskin.lua` in the tests directory. This translates +a curly-bracket form into standard Lua, and at its heart is defining '{' and '}' as +macros. You have to keep a brace stack, because these tokens still have their old +meaning and the table constructor in this example must still work, while the +trailing brace must be converted to `end`. + + if (a > b) { + t = {a,b} + } + +### Pass-Through Macros + +Normally a macro replaces the name (plus any arguments) with the substitution. It +is sometimes useful to pass the name through, but not to push the name into the +token stream - otherwise we will get an endless expansion. + + macro.define('fred',function() + print 'fred was found' + return nil, true + end) + +This has absolutely no effect on the preprocessed text ('fred' remains 'fred', but +has a side-effect. This happens if the substitution function returns a second +`true` value. You can look at the immediate lexical environment with `peek`: + + macro.define('fred',function(get) + local t,v = get:peek(1) + if t == 'string' then + local str = get:string() + return 'fred_'..str + end + return nil,true + end) + +Pass-through macros are useful when each macro corresponds to a Lua variable; they +allow such variables to have a dual role. + +An example would be Python-style lists. The [Penlight +List](http://stevedonovan.github.com/Penlight/api/modules/pl.List.html) class has +the same functionality as the built-in Python list, but does not have any +syntactical support: + + > List = require 'pl.List' + > ls = List{10,20,20} + > = ls:slice(1,2) + {10,20} + > ls:slice_assign(1,2,{10,11,20,21}) + > = ls + {10,11,20,21,30} + +It would be cool if we could add a little bit of custom syntax to make this more +natural. What we first need is a 'macro factory' which outputs the code to create +the lists, and also suitable macros with the same names. + + -- list <var-list> [ = <init-list> ] + M.define ('list',function(get) + get() -- skip space + -- 'list' acts as a 'type' followed by a variable list, which may be + -- followed by initial values + local values + local vars,endt = get:idens (function(t,v) + return t == '=' or (t == 'space' and v:find '\n') + end) + -- there is an initialization list + if endt[1] == '=' then + values,endt = get:list '\n' + else + values = {} + end + -- build up the initialization list + for i,name in ipairs(vars) do + M.define_scoped(name,list_check) + values[i] = 'List('..tostring(values[i] or '')..')' + end + local lcal = M._interactive and '' or 'local ' + return lcal..table.concat(vars,',')..' = '..table.concat(values,',')..tostring(endt) + end) + +Note that this is a fairly re-usable pattern; it requires the type constructor +(`List` in this case) and a type-specific macro function (`list_check`). The only +tricky bit is handling the two cases, so the `idens` method finds the end using a +function, not a simple token. `idens`, like `list`, returns the list and the token +that ended the list, so we can use `endt` to check. + + list a = {1,2,3} + list b + +becomes + + local a = List({1,2,3}) + local b = List() + +unless we are in interactive mode, where `local` is not appropriate! + +Each of these list macro/variables may be used in several ways: + + - directly `a` - no action! + - `a[i]` - plain table index + - `a[i:j]` - a list slice. Will be `a:slice(i,j)` normally, but must + be `a:slice_assign(i,j,RHS)` if on the right-hand side of an assignment. + +The substitution function checks these cases by appropriate look-ahead: + + function list_check (get,put) + local t,v = get:peek(1) + if t ~= '[' then return nil, true end -- pass-through; plain var reference + get:expecting '[' + local args = get:list(']',':') + -- it's just plain table access + if #args == 1 then return '['..tostring(args[1])..']',true end + + -- two items separated by a colon; use sensible defaults + M.assert(#args == 2, "slice has two arguments!") + local start,finish = tostring(args[1]),tostring(args[2]) + if start == '' then start = '1' end + if finish == '' then finish = '-1' end + + -- look ahead to see if we're on the left hand side of an assignment + if get:peek(1) == '=' then + get:next() -- skip '=' + local rest,eoln = get:upto '\n' + rest,eoln = tostring(rest),tostring(eoln) + return (':slice_assign(%s,%s,%s)%s'):format(start,finish,rest,eoln),true + else + return (':slice(%s,%s)'):format(start,finish),true + end + end + +This can be used interactively, like so (it requires the Penlight list library.) + + $> luam -llist -i + Lua 5.1.4 Copyright (C) 1994-2008 Lua.org, PUC-Rio + Lua Macro 2.3.0 Copyright (C) 2007-2011 Steve Donovan + > list a = {'one','two'} + > = a:map(\x(x:sub(1,1))) + {o,t} + > a:append 'three' + > a:append 'four' + > = a + {one,two,three,four} + > = a[2:3] + {two,three} + > = a[2:2] = {'zwei','twee'} + {one,zwei,twee,three,four} + > = a[1:2]..{'five'} + {one,zwei,five} + +### Preprocessing C + +With the 2.2 release, LuaMacro can preprocess C files, by the inclusion of a C LPeg +lexer based on work by Peter Odding. This may seem a semi-insane pursuit, given +that C already has a preprocessor, (which is widely considered a misfeature.) +However, the macros we are talking about are clever, they can maintain state, and +can be scoped lexically. + +One of the irritating things about C is the need to maintain separate include +files. It would be better if we could write a module like this: + + + // dll.c + #include "dll.h" + + export { + typedef struct { + int ival; + } MyStruct; + } + + export int one(MyStruct *ms) { + return ms->ival + 1 + } + + export int two(MyStruct *ms) { + return 2*ms->ival; + } + +and have the preprocessor generate an apppropriate header file: + + + #ifndef DLL_H + #define DLL_H + typedef struct { + int ival; + } MyStruct; + + int one(MyStruct *ms) ; + int two(MyStruct *ms) ; + #endif + +The macro `export` is straightforward: + + + M.define('export',function(get) + local t,v = get:next() + local decl,out + if v == '{' then + decl = tostring(get:upto '}') + decl = M.substitute_tostring(decl) + f:write(decl,'\n') + else + decl = v .. ' ' .. tostring(get:upto '{') + decl = M.substitute_tostring(decl) + f:write(decl,';\n') + out = decl .. '{' + end + return out + end) + +It looks ahead and if it finds a `{}` block it writes the block as text to a file +stream; otherwise writes out the function signature. `get:upto '}'` will do the +right thing here since it keeps track of brace level. To allow any other macro +expansions to take place, `substitute_tostring` is directly called. + +`tests/cexport.lua` shows how this idea can be extended, so that the generated +header is only updated when it changes. + +To preprocess C with `luam`, you need to specify the `-C` flag: + + luam -C -lcexport -o dll.c dll.lc + +Have a look at [lc](modules/macro.lc.html) which defines a simplified way to write +Lua bindings in C. Here is `tests/str.l.c`: + + // preprocess using luam -C -llc -o str.c str.l.c + #include <string.h> + + module "str" { + + def at (Str s, Int i = 0) { + lua_pushlstring(L,&s[i-1],1); + return 1; + } + + def upto (Str s, Str delim = " ") { + lua_pushinteger(L, strcspn(s,delim) + 1); + return 1; + } + + } + +The result looks like this: + + // preprocess using luam -C -llc -o str.c str.l.c + #line 2 "str.lc" + #include <string.h> + + #include <lua.h> + #include <lauxlib.h> + #include <lualib.h> + #ifdef WIN32 + #define EXPORT __declspec(dllexport) + #else + #define EXPORT + #endif + typedef const char *Str; + typedef const char *StrNil; + typedef int Int; + typedef double Number; + typedef int Boolean; + + + #line 6 "str.lc" + static int l_at(lua_State *L) { + const char *s = luaL_checklstring(L,1,NULL); + int i = luaL_optinteger(L,2,0); + + #line 7 "str.lc" + + lua_pushlstring(L,&s[i-1],1); + return 1; + } + + static int l_upto(lua_State *L) { + const char *s = luaL_checklstring(L,1,NULL); + const char *delim = luaL_optlstring(L,2," ",NULL); + + #line 12 "str.lc" + + lua_pushinteger(L, strcspn(s,delim) + 1); + return 1; + } + + static const luaL_reg str_funs[] = { + {"at",l_at}, + {"upto",l_upto}, + {NULL,NULL} + }; + + EXPORT int luaopen_str (lua_State *L) { + luaL_register (L,"str",str_funs); + + return 1; + } + +Note the line directives; this makes working with macro-ized C code much easier +when the inevitable compile and run-time errors occur. `lc` takes away some +of the more irritating bookkeeping needed in writing C extensions +(here I only have to mention function names once) + +`lc` was used for the [winapi](https://github.com/stevedonovan/winapi) project to +preprocess [this +file](https://github.com/stevedonovan/winapi/blob/master/winapi.l.c) +into [standard C](https://github.com/stevedonovan/winapi/blob/master/winapi.c). + +This used an extended version of `lc` which handled the largely superficial +differences between the Lua 5.1 and 5.2 API. + +(The curious thing is that `winapi` is my only project where I've leant on +LuaMacro, and it's all in C.) + +### A Simple Test Framework + +LuaMacro comes with yet another simple test framework - I apologize for this in +advance, because there are already quite enough. But consider it a demonstration +of how a little macro sugar can make tests more readable, even if you are +uncomfortable with them in production code (see `tests/test-test.lua`) + + require_ 'assert' + assert_ 1 == 1 + assert_ "hello" matches "^hell" + assert_ x.a throws 'attempt to index global' + +The last line is more interesting, since it's transparently wrapping +the offending expression in an anonymous function. The expanded output looks +like this: + + T_ = require 'macro.lib.test' + T_.assert_eq(1 ,1) + T_.assert_match("hello" ,"^hell") + T_.assert_match(T_.pcall_no(function() return x.a end),'attempt to index global') + +(This is a generally useful pattern - use macros to provide a thin layer of sugar +over the underlying library. The `macro.assert` module is only 75 lines long, with +comments - its job is to format code to make using the implementation easier.) + +Remember that the predefined meaning of @ is to convert `@name` into `name_`. So we +could just as easily say `@assert 1 == 1` and so forth. + +Lua functions often return multiple values or tables: + + two = \(40,2) + table2 = \({40,2}) + @assert two() == (40,2) + @assert table2() == {40,2} + +For a proper grown-up Lua testing framework +that uses LuaMacro, see [Specl](http://gvvaughan.github.io/specl). + + +### Implementation + +It is not usually necessary to understand the underlying representation of token +lists, but I present it here as a guide to understanding the code. + +#### Token Lists + +The token list representation of the expression `x+1` is: + + {{'iden','x'},{'+','+'},{'number','1'}} + +which is the form returned by the LPeg lexical analyser. Please note that there are +also 'space' and 'comment' tokens in the stream, which is a big difference from the +token-filter standard. + +The `TokenList` type defines `__tostring` and some helper methods for these lists. + +The following macro is an example of the lower-level coding needed without the +usual helpers: + + local macro = require 'macro' + macro.define('qw',function(get,put) + local append = table.insert + local t,v = get() + local res = {{'{','{'}} + t,v = get:next() + while t ~= ')' do + if t ~= ',' then + append(res,{'string','"'..v..'"'}) + append(res,{',',','}) + end + t,v = get:next() + end + append(res,{'}','}'}) + return res + end) + +We're using the getter `next` method to skip any whitespace, but building up the +substitution without a putter, just manipulating the raw token list. `qw` takes a +plain list of words, separated by spaces (and maybe commas) and makes it into a +list of strings. That is, + + qw(one two three) + +becomes + + {'one','two','three'} + +#### Program Structure + +The main loop of `macro.substitute` (towards end of `macro.lua`) summarizes the +operation of LuaMacro: + +There are two macro tables, `imacro` for classic name macros, and `smacro` for +operator style macros. They contain macro tables, which must have a `subst` field +containing the substitution and may have a `parms` field, which means that they +must be followed by their arguments in parentheses. + +A keywords table is chiefly used to track block scope, e.g. +`do`,`if`,`function`,etc means 'increase block level' and `end`,`until` means +'decrease block level'. At this point, any defined block handlers for this level +will be evaluated and removed. These may insert tokens into the stream, like +macros. This is how something like `_END_CLOSE_` is implemented: the `end` causes +the block level to decrease, which fires a block handler which passes `end` through +and inserts a closing `)`. + +Any keyword may also have an associated keyword handler, which works rather like a +macro substitution, except that the keyword itself is always passed through first. +(Allowing keywords as regular macros would generally be a bad idea because of the +recursive substitution problem.) + +The macro `subst` field may be a token list or a function. if it is a function then +that function is called, with the parameters as token lists if the macro defined +formal parameters, or with getter and setter objects if not. If the result is text +then it is parsed into a token list. diff --git a/Tools/LuaMacro/tests/cexport.lua b/Tools/LuaMacro/tests/cexport.lua new file mode 100644 index 0000000..cb20bd0 --- /dev/null +++ b/Tools/LuaMacro/tests/cexport.lua @@ -0,0 +1,77 @@ +local M = require 'macro' + +local cf,copy,null +if package.config:sub(1,1) == '\\' then + cf = 'fc'; copy = 'copy'; null = ' > null' +else + cf = 'diff'; copy = 'cp'; null = ' > /dev/null' +end + +local f,hname,mname + +M.keyword_handler('BEGIN',function() + hname = M.filename:gsub('%.%a+$','')..'.h' + mname = hname:gsub('%.','_'):upper() + f = io.open(M.filename..'.h','w') + f:write('#ifndef ',mname,'\n') + f:write('#define ',mname,'\n') +end) + +M.keyword_handler ('END',function() + f:write('#endif\n') + f:close() + local tmpf = M.filename..'.h' + if os.execute(cf..' '..hname..' '..tmpf..null) ~= 0 then + os.execute(copy..' '..tmpf..' '..hname..null) + end +end) + +M.define('export',function(get) + local t,v = get:next() + local decl,out + if v == '{' then -- block! + decl = tostring(get:upto '}') + decl = M.substitute_tostring(decl) + f:write(decl,'\n') + else + decl = v .. ' ' .. tostring(get:upto '{') + decl = M.substitute_tostring(decl) + f:write(decl,';\n') + out = decl .. '{' + end + return out +end) + + +--[[ + +Example of a with-statement: + + with(MyType *,bonzo) { + .x = 2; + .y = 3; + with(SubType *,.data) { + .name = "hello"; + .ids = my.ids; + printf("count %d\n",.count); + } + } + + +M.define('with',function(get) + get:expecting '(' + local args = get:list() + local T, expr = args[1],args[2] + get:expecting '{' + M.define_scoped('.',function() + local lt,lv = get:peek(-1,true) -- peek before the period... + if lt ~= 'iden' then + return '_var->' + else + return nil,true -- pass through + end + end) + return '{ ' .. tostring(T) .. ' _var = '..tostring(expr)..'; ' +end) + +]] diff --git a/Tools/LuaMacro/tests/class1.lc b/Tools/LuaMacro/tests/class1.lc new file mode 100644 index 0000000..60a73a0 --- /dev/null +++ b/Tools/LuaMacro/tests/class1.lc @@ -0,0 +1,40 @@ +// preprocess using luam -C -llc class1.lc > class1.c +module "class1" { + +class A { + int handle; + + constructor (Int i) { + this->handle = i; + } + + def geth () { + lua_pushinteger(L, this->handle); + return 1; + } + + def __eq(A other) { + lua_pushboolean(L, this->handle == other->handle); + return 1; + } +} + +def A (Int i) { + push_new_A(L,i); + return 1; +} + +constants { + Int MAGIC = 42 +} + +} + +lua_tests { + require 'class1' + M = class1.MAGIC + o = class1.A(M) + assert(o:geth() == M) + a = class1.A(M) + assert(a == o); +} diff --git a/Tools/LuaMacro/tests/const.lua b/Tools/LuaMacro/tests/const.lua new file mode 100644 index 0000000..f5f8508 --- /dev/null +++ b/Tools/LuaMacro/tests/const.lua @@ -0,0 +1,9 @@ +local macro = require 'macro' +macro.define ('const',function(get) + get() + local vars,values = get:idens '=',get:list '\n' + for i,name in ipairs(vars) do + macro.assert(values[i],'each constant must be assigned!') + macro.define_scoped(name,tostring(values[i])) + end +end) diff --git a/Tools/LuaMacro/tests/cskin.lua b/Tools/LuaMacro/tests/cskin.lua new file mode 100644 index 0000000..d77f7f9 --- /dev/null +++ b/Tools/LuaMacro/tests/cskin.lua @@ -0,0 +1,127 @@ +-- cskin.lua +local M = require 'macro' + +M.define_tokens{'&&','||','!=','{|'} + +M.define '&& and' +M.define '|| or' +M.define '!= ~=' +M.define '! not' + +local push,pop = table.insert,table.remove +local bstack = {} +local btop = {} + +local function push_brace_stack (newv) + newv = newv or {} + newv.lev = 0 + push(bstack,btop) + btop = newv +end + +local disabled = false + +-- skinning can be temporarily disabled; this macro re-enables skinning +M.define('_SKIN_',function() disabled = false end) + +local function block_statement (word,end_handler) + return function(get,put) + if disabled then return end + get:expecting '(' + local stuff = get:upto ')' + get:expecting '{' + push_brace_stack {handler = end_handler} + return put:space():tokens(stuff):space():keyword(word) + end +end + +local function endif_handler (get,put) + local t,v = get:next() + if t == 'keyword' and v == 'else' then + local nt,nv = get:next() + if nt == 'keyword' and nv == 'if' then + return put:keyword 'elseif' + else + M.assert(nt == '{') + end + push_brace_stack() -- opening else block + return put:keyword 'else' + else + return put:keyword 'end' (t,v) + end +end + +M.keyword_handler ('for',block_statement 'do') +M.keyword_handler ('while',block_statement 'do') +M.keyword_handler ('if',block_statement ('then',endif_handler)) +M.keyword_handler ('elseif',block_statement ('then',endif_handler)) + +M.define('{',function() + if btop.lev then + btop.lev = btop.lev + 1 + end + return nil,true --> pass-through macro +end) + +M.define('}',function(get,put) + if btop.lev == 0 then + local res + if btop.handler then res = btop.handler(get,put) end + if not res then res = put:space():keyword'end' end + btop = pop(bstack) + return res + else + btop.lev = btop.lev - 1 + return nil,true --> pass-through macro + end +end) + +-- def for function is a little easier; it's a plain macro, +-- and we deliberately don't want to get rid of the parens. +M.define('def',function(get,put) + local stuff = get:list('{','') + put:keyword('function') + if btop.classname then put:iden(btop.classname) '.' end + push_brace_stack() + return put:list(stuff) +end) + +----- OOP support ------ +M.define('class',function(get,put) + local name,t,v = get:iden(),get:next() + local base = '' + if t == ':' then base = get:iden(); t = get:next() end + M.assert(t == '{','expecting {') + push_brace_stack {classname = name} + return 'do '..name..' = class_('..base..')' +end) + +class_ = require 'macro.lib.class' + +---- making an existing macro play nicely with the C skin --- +require 'macro.forall' + +local fun = M.get_macro_value 'forall' +M.define('forall',function (get,put) + get:expecting '(' + local stuff = get:upto ')' + get:expecting'{' + stuff:space():keyword 'do' + stuff = fun(get.from_tl(stuff),put) + -- let the unskinned Lua pass through with _SKIN_ to re-enable skinning + disabled = true + stuff:iden '_SKIN_':space() + push_brace_stack() + return stuff +end) + +-- often easier to express the macro in a skinned form +M.define('{|',function(get,put) + local expr = tostring(get:upto '|') + local select = tostring(get:upto '}') + return ('(def(){local r={}; forall(%s) {r[#r+1]=%s} return r})()'):format(select,expr) +end) + + + + diff --git a/Tools/LuaMacro/tests/dll.c b/Tools/LuaMacro/tests/dll.c new file mode 100644 index 0000000..629feae --- /dev/null +++ b/Tools/LuaMacro/tests/dll.c @@ -0,0 +1,37 @@ +// luam -C -lcexport dll.c +// expands this file into pukka C and creates/updates dll.h + +#include "dll.h" + +export { +typedef struct { + int ival; +} MyStruct; +} + +// yes we could use #define here, but it's sometimes useful to have another level +// of macro substitution +def_ alloc(T) (T*)malloc(sizeof(T)) + +// Plus, LuaMacro can do operator replacements. This is Ruby-style 'field' access +def_ @ self-> + +export MyStruct *create() { + return alloc(MyStruct); +} + +def_ This MyStruct *self + +export int one(This) { + return @ival + 1 +} + +export int two(This) { + return 2*@ival; +} + +export void set(This,int i) { + @ival = i; +} + + diff --git a/Tools/LuaMacro/tests/dollar.lua b/Tools/LuaMacro/tests/dollar.lua new file mode 100644 index 0000000..954416d --- /dev/null +++ b/Tools/LuaMacro/tests/dollar.lua @@ -0,0 +1,22 @@ +local macro = require 'macro'
+
+macro.define('$',function(get)
+ local t,v = get()
+ if t == 'iden' then
+ return 'os.getenv("'..v..'")'
+ elseif t == '(' then
+ local rest = get:upto ')'
+ return 'eval("'..tostring(rest)..'")'
+ end
+end)
+
+return function()
+ return [[
+local function eval(cmd)
+ local f = io.popen(cmd,'r')
+ local res = f:read '*a'
+ f:close()
+ return res
+end
+]]
+end
diff --git a/Tools/LuaMacro/tests/exit.tmp b/Tools/LuaMacro/tests/exit.tmp new file mode 100644 index 0000000..d56d271 --- /dev/null +++ b/Tools/LuaMacro/tests/exit.tmp @@ -0,0 +1,3 @@ +print 'hello'
+os.exit()
+
diff --git a/Tools/LuaMacro/tests/forall1.lua b/Tools/LuaMacro/tests/forall1.lua new file mode 100644 index 0000000..65589e2 --- /dev/null +++ b/Tools/LuaMacro/tests/forall1.lua @@ -0,0 +1,8 @@ +local macro = require 'macro'
+
+macro.define('forall',function(get)
+ local var = get:iden()
+ local t,v = get:next() -- will be 'in'
+ local rest = tostring(get:upto 'do')
+ return ('for _,%s in ipairs(%s) do'):format(var,rest)
+end)
diff --git a/Tools/LuaMacro/tests/lc.lua b/Tools/LuaMacro/tests/lc.lua new file mode 100644 index 0000000..fc8973d --- /dev/null +++ b/Tools/LuaMacro/tests/lc.lua @@ -0,0 +1,297 @@ +-- Simplifying writing C extensions for Lua +-- Adds new module and class constructs; +-- see class1.lc and str.lc for examples. +local M = require 'macro' + +function dollar_subst(s,tbl) + return (s:gsub('%$%((%a+)%)',tbl)) +end + +-- reuse some machinery from the C-skin experiments +local push,pop = table.insert,table.remove +local bstack,btop = {},{} + +local function push_brace_stack (newv) + newv = newv or {} + newv.lev = 0 + push(bstack,btop) + btop = newv +end + +M.define('{',function() + if btop.lev then + btop.lev = btop.lev + 1 + end + return nil,true --> pass-through macro +end) + +M.define('}',function(get,put) + if not btop.lev then + return nil,true + elseif btop.lev == 0 then + local res + if btop.handler then res = btop.handler(get,put) end + if not res then res = put:space() '}' end + btop = pop(bstack) + return res + else + btop.lev = btop.lev - 1 + return nil,true --> pass-through macro + end +end) + +--------- actual implementation begins ------- + +local append = table.insert +local module + +local function register_functions (names,cnames) + local out = {} + for i = 1,#names do + append(out,(' {"%s",l_%s},'):format(names[i],cnames[i])) + end + return table.concat(out,'\n') +end + +local function finalizers (names) + local out = {} + for i = 1,#names do + append(out,names[i].."(L);") + end + return table.concat(out,'\n') +end + +local typedefs + +local preamble = [[ +#include <lua.h> +#include <lauxlib.h> +#include <lualib.h> +#ifdef WIN32 +#define EXPORT __declspec(dllexport) +#else +#define EXPORT +#endif +]] + +local finis = [[ +static const luaL_reg $(cname)_funs[] = { + $(funs) + {NULL,NULL} +}; + +EXPORT int luaopen_$(cname) (lua_State *L) { + luaL_register (L,"$(name)",$(cname)_funs); + $(finalizers) + return 1; +} +]] + +M.define('module',function(get) + local name = get:string() + local cname = name:gsub('%.','_') + get:expecting '{' + local out = preamble .. typedefs + push_brace_stack{ + name = name, cname = cname, + names = {}, cnames = {}, finalizers = {}, + handler = function() + local out = {} + local funs = register_functions(btop.names,btop.cnames) + local final = finalizers(btop.finalizers) + append(out,dollar_subst(finis, { + cname = cname, + name = name, + funs = funs, + finalizers = final + })) + return table.concat(out,'\n') + end } + module = btop + return out +end) + + +M.define('def',function(get) + local fname = get:iden() + local cname = (btop.ns and btop.ns..'_' or '')..fname + append(btop.names,fname) + append(btop.cnames,cname) + get:expecting '(' + local args = get:list():strip_spaces() + get:expecting '{' + local t,space = get() + indent = space:gsub('^%s*[\n\r]',''):gsub('%s$','') + local out = {"static int l_"..cname.."(lua_State *L) {"} + if btop.massage_arg then + btop.massage_arg(args) + end + for i,arg in ipairs(args) do + local mac = arg[1][2]..'_init' + if arg[3] and arg[3][1] == '=' then + mac = mac .. 'o' + i = i .. ',' .. arg[4][2] + end + append(out,indent..mac..'('..arg[2][2]..','..i..');') + end + append(out,space) + return table.concat(out,'\n') +end) + +M.define('constants',function(get,put) + get:expecting '{' + local consts = get:list '}' :strip_spaces() + --for k,v in pairs(btop) do io.stderr:write(k,'=',tostring(v),'\n') end + -- os.exit() + local fname = 'set_'..btop.cname..'_constants' + local out = { 'static void '..fname..'(lua_State *L) {'} + append(btop.finalizers,fname) + for _,c in ipairs(consts) do + local type,value,name + if #c == 1 then -- a simple int constant: CONST + name = c:pick(1) + type = 'Int' + value = name + else -- Type CONST [ = VALUE ] + type = c:pick(1) + name = c:pick(2) + if #c == 2 then + value = name + else + value = c:pick(4) + end + end + append(out,('%s_set("%s",%s);'):format(type,name,value )) + end + append(out,'}') + return table.concat(out,'\n') +end) + +M.define('assign',function(get) + get:expecting '{' + local asses = get:list '}' :strip_spaces() + local out = {} + for _,c in ipairs(asses) do + append(out,('%s_set("%s",%s);\n'):format(c:pick(1),c:pick(2),c:pick(4)) ) + end + return table.concat(out,'\n') +end) + +typedefs = [[ +typedef const char *Str; +typedef const char *StrNil; +typedef int Int; +typedef double Number; +typedef int Boolean; +]] + + +M.define 'Str_init(var,idx) const char *var = luaL_checklstring(L,idx,NULL)' +M.define 'Str_inito(var,idx,val) const char *var = luaL_optlstring(L,idx,val,NULL)' +M.define 'Str_set(name,value) lua_pushstring(L,value); lua_setfield(L,-2,name)' +M.define 'Str_get(var,name) lua_getfield(L,-1,name); var=lua_tostring(L,-1); lua_pop(L,1)' + +M.define 'StrNil_init(var,idx) const char *var = lua_tostring(L,idx)' + +M.define 'Int_init(var,idx) int var = luaL_checkinteger(L,idx)' +M.define 'Int_inito(var,idx,val) int var = luaL_optinteger(L,idx,val)' +M.define 'Int_set(name,value) lua_pushinteger(L,value); lua_setfield(L,-2,name)' +M.define 'Int_get(var,name) lua_getfield(L,-1,name); var=lua_tointeger(L,-1); lua_pop(L,1)' + +M.define 'Number_init(var,idx) double var = luaL_checknumber(L,idx)' +M.define 'Number_inito(var,idx,val) double var = luaL_optnumber(L,idx,val)' +M.define 'NUmber_set(name,value) lua_pushnumber(L,value); lua_setfield(L,-2,name)' + +M.define 'Boolean_init(var,idx) int var = lua_toboolean(L,idx)' +M.define 'Boolean_set(name,value) lua_pushboolean(L,value); lua_setfield(L,-2,name)' + +M.define 'Value_init(var,idx) int var = idx' + +M.define('lua_tests',function(get) + get:expecting '{' + local body = get:upto '}' + local f = io.open(M.filename..'.lua','w') + f:write(tostring(body)) + f:close() +end) + +------ class support ---------------------- + +local klass_ctor = "static void $(klass)_ctor(lua_State *L, $(klass) *this, $(fargs))" + +local begin_klass = [[ + +typedef struct { + $(fields) +} $(klass); + +define_ $(klass)_init(var,idx) $(klass) *var = $(klass)_arg(L,idx) + +#define $(klass)_MT "$(klass)" + +$(klass) * $(klass)_arg(lua_State *L,int idx) { + $(klass) *this = ($(klass) *)luaL_checkudata(L,idx,$(klass)_MT); + luaL_argcheck(L, this != NULL, idx, "$(klass) expected"); + return this; +} + +$(ctor); + +static void push_new_$(klass)(lua_State *L,$(fargs)) { + $(klass) *this = ($(klass) *)lua_newuserdata(L,sizeof($(klass))); + luaL_getmetatable(L,$(klass)_MT); + lua_setmetatable(L,-2); + $(klass)_ctor(L,this,$(aargs)); +} + +]] + +local end_klass = [[ + +static const struct luaL_reg $(klass)_methods [] = { + $(methods) + {NULL, NULL} /* sentinel */ +}; + +static void $(klass)_register (lua_State *L) { + luaL_newmetatable(L,$(klass)_MT); + luaL_register(L,NULL,$(klass)_methods); + lua_pushvalue(L,-1); + lua_setfield(L,-2,"__index"); + lua_pop(L,1); +} +]] + +M.define('class',function(get) + local name = get:iden() + get:expecting '{' + local fields = get:upto (function(t,v) + return t == 'iden' and v == 'constructor' + end) + get:expecting '(' + local out = {} + local args = get:list() + local f_args = args:strip_spaces() + local a_args = f_args:pick(2) + f_args = table.concat(args:__tostring(),',') + a_args = table.concat(a_args,',') + local subst = {klass=name,fields=tostring(fields),fargs=f_args,aargs=a_args } + local proto = dollar_subst(klass_ctor,subst) + subst.ctor = proto + append(out,dollar_subst(begin_klass,subst)) + append(out,proto) + local pp = {{'iden',name},{'iden','this'}} + push_brace_stack{ + names = {}, cnames = {}, ns = name, cname = name, + massage_arg = function(args) + table.insert(args,1,pp) + end, + handler = function(get,put) + append(module.finalizers,name.."_register") + local methods = register_functions(btop.names,btop.cnames) + return dollar_subst(end_klass,{methods=methods,klass=name,fargs=f_args,aargs=a_args}) + end + } + return table.concat(out,'\n') +end) + diff --git a/Tools/LuaMacro/tests/list.lua b/Tools/LuaMacro/tests/list.lua new file mode 100644 index 0000000..274d482 --- /dev/null +++ b/Tools/LuaMacro/tests/list.lua @@ -0,0 +1,59 @@ +local M = require 'macro'
+List = require 'pl.List'
+
+local list_check
+
+-- list <var-list> [ = <init-list> ]
+-- acts as a 'macro factory', making locally-scoped macros for the variables,
+-- and emitting code to initialize plain variables.
+M.define ('list',function(get)
+ get() -- skip space
+ -- 'list' acts as a 'type' followed by a variable list, which may be
+ -- followed by initial values
+ local values
+ local vars,endt = get:idens (function(t,v)
+ return t == '=' or (t == 'space' and v:find '\n')
+ end)
+ -- there is an initialization list
+ if endt[1] == '=' then
+ values,endt = get:list '\n'
+ else
+ values = {}
+ end
+ -- build up the initialization list
+ for i,name in ipairs(vars) do
+ M.define_scoped(name,list_check)
+ values[i] = 'List('..tostring(values[i] or '')..')'
+ end
+ local lcal = M._interactive and '' or 'local '
+ local res = lcal..table.concat(vars,',')..' = '..table.concat(values,',')..tostring(endt)
+ return res
+end)
+
+function list_check (get,put)
+ local t,v = get:peek(1)
+ if t ~= '[' then return nil, true end -- pass-through; plain var reference
+ get:expecting '['
+ local args = get:list(']',':')
+ -- it's just plain table access
+ if #args == 1 then return '['..tostring(args[1])..']',true end
+
+ -- two items separated by a colon; use sensible defaults
+ M.assert(#args == 2, "slice has two arguments!")
+ local start,finish = tostring(args[1]),tostring(args[2])
+ if start == '' then start = '1' end
+ if finish == '' then finish = '-1' end
+
+ -- look ahead to see if we're on the left hand side of an assignment
+ if get:peek(1) == '=' then
+ get:next() -- skip '='
+ local rest,eoln = get:upto '\n'
+ rest,eoln = tostring(rest),tostring(eoln)
+ return (':slice_assign(%s,%s,%s)%s'):format(start,finish,rest,eoln),true
+ else
+ return (':slice(%s,%s)'):format(start,finish),true
+ end
+end
+
+
+
diff --git a/Tools/LuaMacro/tests/mmath.lua b/Tools/LuaMacro/tests/mmath.lua new file mode 100644 index 0000000..ad813b5 --- /dev/null +++ b/Tools/LuaMacro/tests/mmath.lua @@ -0,0 +1,7 @@ +-- shows how a macro module pulled in with require_ +-- can return a substitution value. In this case, +-- it would be better to use include_, but this +-- method is more general +return function() + return 'local sin,cos = math.sin, math.cos\n' +end diff --git a/Tools/LuaMacro/tests/mod.m.lua b/Tools/LuaMacro/tests/mod.m.lua new file mode 100644 index 0000000..50151e6 --- /dev/null +++ b/Tools/LuaMacro/tests/mod.m.lua @@ -0,0 +1,48 @@ +require_ 'module' + +local function dump(text) + print (text) +end + +function one () + return two() +end + +class Fred + + function _init(self,x) + @set(x or 1) + end + + function set(self,x) + @x = x + end + + function get(self) + return @x + end + + function set2(self) + @set(0) + end + +end + +class Alice : Fred + function __tostring(self) + return "Alice "..tostring(@x) + end + + function set2(self) + @set(1) + end +end + + +function two () + return 42 +end + + + + diff --git a/Tools/LuaMacro/tests/proto.lua b/Tools/LuaMacro/tests/proto.lua new file mode 100644 index 0000000..dff532c --- /dev/null +++ b/Tools/LuaMacro/tests/proto.lua @@ -0,0 +1,31 @@ +local M = require 'macro' + +function _assert_arg(val,idx,t) + if type(val) ~= t then + error(("type mismatch argument %d: got %s, expecting %s"):format(idx,type(val),t),2) + end +end + +M.define('Function',function(get,put) + local name = get:upto '(' + local args,endt = get:list() + args = args:strip_spaces() + local argnames,names = {},{} + for i,a in ipairs(args) do + local name = a:pick(1) + M.assert(a:pick(2) == ':') + table.remove(a,1) + table.remove(a,1) + argnames[i] = {{'iden',name}} + names[i] = name + end + get:expecting ':' + local rtype, endt = get:upto '\n' + put :keyword 'function' :space() :tokens(name) '(' :list(argnames) ')' :space '\n' + put :space() + for i,a in ipairs(args) do + local tp = a:pick(1) + put :iden('_assert_arg') '(' :iden(names[i]) ',' :number(i) ',' :string(tp) ')' ';' + end + return put +end) diff --git a/Tools/LuaMacro/tests/qw.lua b/Tools/LuaMacro/tests/qw.lua new file mode 100644 index 0000000..80fb26d --- /dev/null +++ b/Tools/LuaMacro/tests/qw.lua @@ -0,0 +1,16 @@ +local macro = require 'macro'
+macro.define('qw',function(get,put)
+ local append = table.insert
+ local t,v = get()
+ local res = {{'{','{'}}
+ t,v = get:next()
+ while t ~= ')' do
+ if t ~= ',' then
+ append(res,{'string','"'..v..'"'})
+ append(res,{',',','})
+ end
+ t,v = get:next()
+ end
+ append(res,{'}','}'})
+ return res
+end)
\ No newline at end of file diff --git a/Tools/LuaMacro/tests/rawhash.lua b/Tools/LuaMacro/tests/rawhash.lua new file mode 100644 index 0000000..fdd86b3 --- /dev/null +++ b/Tools/LuaMacro/tests/rawhash.lua @@ -0,0 +1,34 @@ +local M = require 'macro' + +local concat = table.concat + +M.define ('Tab',function(get) + get() -- skip space + -- 'Tab' acts as a 'type' followed by a variable list + local vars,endt = get:idens (function(t,v) + return t == '=' or (t == 'space' and v:find '\n') + end) + local values = {} + for i,name in ipairs(vars) do + M.define_scoped(name,function(get,put) + local t,v = get:peek(1) + if t ~= '[' then return nil, true end -- pass-through; plain var reference + get:expecting '[' + local args = get:list(']','') + local index = args[1] + for i = 1,#index do + if index[i][1] == '#' and (i == #index or index[i+1][1] ~= 'iden') then + table.insert(index,i+1,{'iden',name}) + end + end + return '['..tostring(index)..']',true + end) + values[i] = '{}' + end + local lcal = M._interactive and '' or 'local ' + local res = lcal..concat(vars,',')..' = '..concat(values,',')..tostring(endt) + return res +end) + + + diff --git a/Tools/LuaMacro/tests/readme.md b/Tools/LuaMacro/tests/readme.md new file mode 100644 index 0000000..89c07d7 --- /dev/null +++ b/Tools/LuaMacro/tests/readme.md @@ -0,0 +1,23 @@ +To run the examples, you can either directly use
+
+ $> lua ../luam.lua run-tests.lua
+
+or make a shortcut to luam.lua on your path.
+
+ $> luam run-tests.lua
+
+`run-tests.lua` is both an example of using macros and a little test harness for the package.
+
+The shortcut should look something like this
+
+ @echo off
+ rem luam.bat
+ lua c:\mylua\LuaMacro\luam.lua %*
+
+or this:
+
+ # luam
+ lua /home/frodo/lua/LuaMacro/luam.lua $*
+
+and then should be copied somewhere on your executable path.
+
diff --git a/Tools/LuaMacro/tests/run-tests.lua b/Tools/LuaMacro/tests/run-tests.lua new file mode 100644 index 0000000..8bc3317 --- /dev/null +++ b/Tools/LuaMacro/tests/run-tests.lua @@ -0,0 +1,35 @@ +-- similar syntax to tests.bat, but more portable and aware of errors. +require_ 'forall' +require_ 'qw' +local lua52 = _VERSION:match '5.2' +local lua51 = not lua52 +def_ put io.stderr:write + +local tests = qw(dollar,lambda,try,block,forall,scope,do,const,with,case,mod,test,rawhash) + +local luam = lua51 and 'luam' or 'luam52' + +function run (f) + put(f,': ') + local res = os.execute(luam..' '..f) + if (lua52 and not res) or (lua51 and res ~= 0) then + put 'failed!\n' + os.exit(1) + else + put 'ok\n' + end +end + +forall f in tests do + f = 'test-'..f..'.lua' + run(f) +end + +run '-lcskin test-cskin.lua' + +if pcall(require,'pl') then + run 'test-list.lua' + run 'test-pl-list.lua' +end + + diff --git a/Tools/LuaMacro/tests/str.l.c b/Tools/LuaMacro/tests/str.l.c new file mode 100644 index 0000000..e15891c --- /dev/null +++ b/Tools/LuaMacro/tests/str.l.c @@ -0,0 +1,19 @@ +// preprocess using luam -C -llc -o str.c str.l.c +#include <string.h> + +module "str" { + + def at (Str s, Int i = 0) { + lua_pushlstring(L,&s[i-1],1); + return 1; + } + + def upto (Str s, Str delim = " ") { + lua_pushinteger(L, strcspn(s,delim) + 1); + return 1; + } + +} + + + diff --git a/Tools/LuaMacro/tests/test-assert.lua b/Tools/LuaMacro/tests/test-assert.lua new file mode 100644 index 0000000..fbe5609 --- /dev/null +++ b/Tools/LuaMacro/tests/test-assert.lua @@ -0,0 +1,10 @@ +require_ 'macro.try'
+
+def_ ASSERT(condn,expr) if condn then else error(expr) end
+
+try
+ ASSERT(2 == 1,"damn..".. 2 .." not equal to ".. 1)
+except (e)
+ print('threw:',e)
+end
+
diff --git a/Tools/LuaMacro/tests/test-atm.lua b/Tools/LuaMacro/tests/test-atm.lua new file mode 100644 index 0000000..7832b8d --- /dev/null +++ b/Tools/LuaMacro/tests/test-atm.lua @@ -0,0 +1,13 @@ +@let env = os.getenv +@if env 'P' +print 'P env was set' +@if A +print 'Global A was true' +@end +@elseif A +print 'Global A was true, no P' +@else +print 'Neither P or A' +@end + + diff --git a/Tools/LuaMacro/tests/test-block.lua b/Tools/LuaMacro/tests/test-block.lua new file mode 100644 index 0000000..22c5ae5 --- /dev/null +++ b/Tools/LuaMacro/tests/test-block.lua @@ -0,0 +1,13 @@ +-- in this case, a simple statement macro can be used
+-- `block ... end` expands to `(function() ... end)`
+
+def_ block (function() _END_")"
+
+function peval(fun)
+ print(fun())
+end
+
+peval block
+ return 10,'hello',54
+end
+
diff --git a/Tools/LuaMacro/tests/test-case.lua b/Tools/LuaMacro/tests/test-case.lua new file mode 100644 index 0000000..4f7eb25 --- /dev/null +++ b/Tools/LuaMacro/tests/test-case.lua @@ -0,0 +1,21 @@ +def_ OF_ def_ (of elseif _value ==)
+def_ case(x) do OF_ local _value = x if false then _END_END_
+
+function test(n)
+ local res
+ case(n)
+ of 10 then
+ res = 1
+ of 20 then
+ res = 2
+ else
+ res = 3
+ end
+ return res
+end
+
+assert(test(10)==1)
+assert(test(20)==2)
+assert(test(30)==3)
+
+
diff --git a/Tools/LuaMacro/tests/test-const.lua b/Tools/LuaMacro/tests/test-const.lua new file mode 100644 index 0000000..9069568 --- /dev/null +++ b/Tools/LuaMacro/tests/test-const.lua @@ -0,0 +1,10 @@ +require_ 'const'
+do
+ const N,M = 10,20
+ do
+ const N = 5
+ assert(N == 5)
+ end
+ assert(N == 10 and M == 20)
+end
+assert(N == nil and M == nil)
diff --git a/Tools/LuaMacro/tests/test-cskin.lua b/Tools/LuaMacro/tests/test-cskin.lua new file mode 100644 index 0000000..5e6a7c8 --- /dev/null +++ b/Tools/LuaMacro/tests/test-cskin.lua @@ -0,0 +1,47 @@ +-- run like so: luam -lcskin test-cskin.lua
+
+class Named {
+ def _init(self,name) { -- name for ctor
+ self.name = name
+ }
+
+ def __tostring(self) { -- metamethod
+ return self.name
+ }
+}
+
+class Shamed: Named { -- doesn't have to define a ctor
+ def __tostring(self) {
+ return "shame on "..self.name
+ }
+}
+
+class Person : Named {
+ def _init(self,name,age) { -- ctor must call inherited ctor explicitly
+ Named._init(self,name)
+ self:set_age(age)
+ }
+
+ def set_age(self,age) { -- plain method
+ self.age = age;
+ }
+
+ def __tostring(self) {
+ return Named.__tostring(self)..' age '..self.age
+ }
+}
+
+a = Named 'Alice'
+print(a)
+b = Shamed 'Job'
+print(b)
+
+aa = {|Named(n)| n in {'Johan','Peter','Mary'}}
+
+forall(a in aa) { print(a) }
+
+p = Person ('Bob',12)
+print(p)
+
+
+
diff --git a/Tools/LuaMacro/tests/test-do.lua b/Tools/LuaMacro/tests/test-do.lua new file mode 100644 index 0000000..7a8697c --- /dev/null +++ b/Tools/LuaMacro/tests/test-do.lua @@ -0,0 +1,28 @@ +require_ 'macro.do'
+-- unrolling a loop
+y = 0
+do_( i,1, 10,
+ y = y + i
+)
+assert(y == 55)
+
+-- do_ defined a _local_ macro 'i'
+assert(i == nil)
+
+
+-- tuples usually expand to A_1,A_2,A_3 and so forth
+tuple(3) A,B
+B = 10,20,30
+print(B)
+
+def_ do3(v,s) do_(v,1,3,s)
+
+-- but inside a do_ statements with tuples work element-wise
+-- debug_
+do_(k,1,3,
+ A = B/2
+)
+--[[
+print(A)
+--]]
+
diff --git a/Tools/LuaMacro/tests/test-dollar.lua b/Tools/LuaMacro/tests/test-dollar.lua new file mode 100644 index 0000000..71d6a25 --- /dev/null +++ b/Tools/LuaMacro/tests/test-dollar.lua @@ -0,0 +1,7 @@ +require_ 'dollar'
+print($PATH)
+if $(ls) ~= 0 then
+ print($(dir /B)) -- so there!
+end
+
+
diff --git a/Tools/LuaMacro/tests/test-forall.lua b/Tools/LuaMacro/tests/test-forall.lua new file mode 100644 index 0000000..0139e97 --- /dev/null +++ b/Tools/LuaMacro/tests/test-forall.lua @@ -0,0 +1,33 @@ +require_ 'macro.forall'
+
+def_ dump(t) print '---'; forall val in t do print(val) end
+
+forall x in {10,20,30} do print(x) end
+
+t = {'hello','dolly'}
+print '---'
+forall name in t do print(name) end
+print '---'
+forall x in t if x:match 'o$' do print(x) end
+
+-- a wee bit tautological, but valid!
+print '---'
+forall x in L{x^2 | x in {10,20,30}} do print(x) end
+
+t = L{s:upper() | s in {'one','two','three'} if s ~= 'two'}
+
+dump(t)
+
+forall i = 1,5 do print(i) end
+
+t = L{2*i|i=1,10}
+
+dump(t)
+
+-- identity matrix using nested list comprehensions.
+t = L{L{i==j and 1 or 0 | j=1,3} | i=1,3}
+
+-- note the other form of LCs: using 'for' means that you explicitly want
+-- the generic Lua for-statement.
+ls = L{line for line in io.lines 'test-forall.lua'}
+print('length of this file',#ls)
diff --git a/Tools/LuaMacro/tests/test-forall1.lua b/Tools/LuaMacro/tests/test-forall1.lua new file mode 100644 index 0000000..c16d77c --- /dev/null +++ b/Tools/LuaMacro/tests/test-forall1.lua @@ -0,0 +1,4 @@ +require_ 'forall1'
+
+forall i in {10,20,30} do print(i) end
+
diff --git a/Tools/LuaMacro/tests/test-include.lua b/Tools/LuaMacro/tests/test-include.lua new file mode 100644 index 0000000..9bea9ed --- /dev/null +++ b/Tools/LuaMacro/tests/test-include.lua @@ -0,0 +1,2 @@ +include_ 'test.inc'
+print(answer)
diff --git a/Tools/LuaMacro/tests/test-lambda.lua b/Tools/LuaMacro/tests/test-lambda.lua new file mode 100644 index 0000000..649b77d --- /dev/null +++ b/Tools/LuaMacro/tests/test-lambda.lua @@ -0,0 +1,18 @@ +require_ 'macro.lambda'
+ok = pcall(require,'pl')
+if not ok then return print 'test-lambda needs penlight' end
+ls = List{10,20,30}
+assert(ls:map(\x(x+1)) == List{11,21,31})
+assert((\(42))() == 42 )
+
+F = \x,y(x - y)
+
+G = \x(F(x,10))
+
+assert(G(11) == 1)
+
+ls = List { (\(10,20,30))() }
+assert(ls == List{10,20,30})
+
+
+
diff --git a/Tools/LuaMacro/tests/test-list.lua b/Tools/LuaMacro/tests/test-list.lua new file mode 100644 index 0000000..f175ccc --- /dev/null +++ b/Tools/LuaMacro/tests/test-list.lua @@ -0,0 +1,36 @@ +--- sugar for making pl.List work like Python lists. +-- The list macro is a factory which generates macros which 'shadow' the variable +-- and kick in when they are followed by [...]. +require_ 'list' + +-- the two forms of 'list' initialization +-- (altho it grabs values upto '\n', this only happens outside a () or {}, +-- so multi-line initializations are possible +list ls,lo = {10,20,30},{'A','ay', + 'B','C'} +list two + +-- the above statements created both the macros 'ls' and values 'ls', etc. +two:append(1) +two:append(2) + +-- seen as plain table access +print(ls[2]) + +-- special treatment for slice notation +print(ls[1:2]) + +-- if we are on the LHS, then adjust accordingly +ls[1:2] = {11,21,22} + +print(ls[2:]) + +print(ls, two, lo) + +-- like in Python, this makes a copy of all of the list +print(ls[:]) + + + + + diff --git a/Tools/LuaMacro/tests/test-macro.lua b/Tools/LuaMacro/tests/test-macro.lua new file mode 100644 index 0000000..59b569b --- /dev/null +++ b/Tools/LuaMacro/tests/test-macro.lua @@ -0,0 +1,113 @@ +require 'pl'
+local macro = require 'macro'
+
+tmp = [[
+for i = 1,10 do
+ fred("hello",i)
+ f(10,'hello')
+ print(str(233))
+ bonzo a,b,c;
+ fun2(\x(x+1),\(a:get()),\x(\y(x+y)))
+ frederick block
+ for i = 1,10 do
+ alpha block
+ print(i)
+ end
+ end
+ end
+
+ try
+ banzai(dog)
+ except(ex)
+ print(ex)
+ end
+end
+]]
+
+local M = macro
+local define = M.define
+
+define 'fred alice'
+define 'alice print'
+define 'f(x,y) fred(x..y))'
+define ('str(x)',function(x)
+ return '"'..x[1][2]..'"'
+end)
+define ('bonzo',function(get)
+ local t = get(); M.assert(t == 'space','space required')
+ local args = M.get_names(get,';')
+ local res = {}
+ M.put_keyword(res,'local')
+ M.put_names(res,args)
+ return res
+end)
+
+define ('@',function(get)
+ return '"'..os.date('%c')..'"'
+end)
+
+define ('\\',function(get)
+ --local args = M.get_names(get,'(')
+ local args = get:names('(')
+ local body = M.get_list(get)
+ --[[
+ local res = {}
+ M.put_keyword(res,'function')
+ M.put(res,'(')
+ M.put_names(res,args)
+ M.put (res,')')
+ M.put_keyword(res,'return')
+ M.put_list(res,body)
+ M.put_space(res)
+ M.put_keyword(res,'end')
+ return res
+ --]]
+ local put = M.Putter()
+ --print('*****',put,getmetatable(put).keyword)
+ --return put;
+ put:keyword 'function' '(' : names(args) ')'
+ return put:keyword 'return' : list(body) : space() : keyword 'end'
+end)
+
+define ('block',function(get)
+ M.block_handler(0,function(get)
+ return ')'
+ end)
+ local res = {}
+ M.put(res,'(')
+ M.put_keyword(res,'function')
+ M.put(res,'(')
+ M.put(res,')')
+ return res
+end)
+
+
+define ('_END_',function(get)
+ local str = M.get_string(get)
+ M.block_handler(0,function()
+ return str
+ end)
+end)
+
+define 'E_ _END_ " end"'
+
+define 'try do local stat_,r_ = pcall(function()'
+define 'except(e) end); E_ if stat_ then if r_~=nil then return r_ end else local e = r_ '
+
+
+local out = stringio.create()
+macro.substitute(tmp,out)
+print(out:value())
+
+if arg[1] == '-i' then
+
+io.write '? '
+local line = io.read()
+while line do
+ local sub,err = macro.substitute_tostring(line..'\n')
+ if sub then io.write(sub) else io.write(err,'\n') end
+ io.write '? '
+ line = io.read()
+end
+
+end
diff --git a/Tools/LuaMacro/tests/test-mod.lua b/Tools/LuaMacro/tests/test-mod.lua new file mode 100644 index 0000000..2d51cb0 --- /dev/null +++ b/Tools/LuaMacro/tests/test-mod.lua @@ -0,0 +1,20 @@ +local mod = require 'mod' +-- def_ show(expr) print(_STR_(expr),expr) + +assert(mod.one() == 42) + +f = mod.Fred(22) + +assert(f:get() == 22) +f:set2() +assert(f:get() == 0) + +a = mod.Alice() +a:set2() +assert(a:get() == 1) +a:set(66) +assert(tostring(a) == "Alice 66") + + + + diff --git a/Tools/LuaMacro/tests/test-pl-list.lua b/Tools/LuaMacro/tests/test-pl-list.lua new file mode 100644 index 0000000..26641aa --- /dev/null +++ b/Tools/LuaMacro/tests/test-pl-list.lua @@ -0,0 +1,12 @@ +-- Wrapping list comprehensions so that they return a pl.List +-- the trick here is that the L macro will pop its macro stack at the end, +-- if set. Here we want to wrap L{...} so it returns a list, so we have +-- List(L{...}). By pushing ')', L will emit the close parens for us. +require 'pl' +require_ 'macro.forall' + +def_ LL List( _PUSH_('L',')') L + +print(LL{i|i=1,3}..LL{i|i=10,20,5}) + +print( LL{List{k,v} for k,v in pairs{A=1,B=2}} ) diff --git a/Tools/LuaMacro/tests/test-proto.lua b/Tools/LuaMacro/tests/test-proto.lua new file mode 100644 index 0000000..753c9fd --- /dev/null +++ b/Tools/LuaMacro/tests/test-proto.lua @@ -0,0 +1,10 @@ +require_ "proto" + +Function bonzo (a: number, b: string) : string + return a .. b +end + +print (bonzo(10,"hello")) +print (bonzo("hello")) ---> blows up! + + diff --git a/Tools/LuaMacro/tests/test-qw.lua b/Tools/LuaMacro/tests/test-qw.lua new file mode 100644 index 0000000..bc8a47d --- /dev/null +++ b/Tools/LuaMacro/tests/test-qw.lua @@ -0,0 +1,3 @@ +require_ 'qw'
+
+print(qw(one two three))
diff --git a/Tools/LuaMacro/tests/test-rawhash.lua b/Tools/LuaMacro/tests/test-rawhash.lua new file mode 100644 index 0000000..6697cf8 --- /dev/null +++ b/Tools/LuaMacro/tests/test-rawhash.lua @@ -0,0 +1,35 @@ +require_ "rawhash" + +function test () + Tab mytable, another + + t = {1,3} + + -- Here # is short for #mytable + mytable[#+1] = 1 + mytable[#+1] = 2 + + -- without indexing, behaves just like a table reference + assert(type(mytable)=='table') + + -- it is still possible to use #t explicitly + assert(mytable [#]==mytable[#t]) + + assert(mytable[#-1] == mytable[1]) + + for i = 1,10 do another[#+1] = i end + for i = 1,10 do assert(another[i] == i) end + +end + +test() + +-- although mytable is a macro, its scope is limited to test() +assert(mytable == nil) + + + + + + + diff --git a/Tools/LuaMacro/tests/test-require.lua b/Tools/LuaMacro/tests/test-require.lua new file mode 100644 index 0000000..f871cf0 --- /dev/null +++ b/Tools/LuaMacro/tests/test-require.lua @@ -0,0 +1,3 @@ +require_ 'mmath' + +print(sin(1.2) + cos(0.3)) diff --git a/Tools/LuaMacro/tests/test-scope.lua b/Tools/LuaMacro/tests/test-scope.lua new file mode 100644 index 0000000..8007225 --- /dev/null +++ b/Tools/LuaMacro/tests/test-scope.lua @@ -0,0 +1,17 @@ +-- simple macros created using def_ are lexically scoped
+do
+ def_ X 42
+ assert(X == 42)
+ do
+ def_ X 'hello'
+ assert(X == 'hello')
+ do
+ def_ X 999
+ assert (X == 999)
+ end
+ assert(X == 'hello')
+ end
+ assert(X == 42)
+end
+assert (X==nil)
+
diff --git a/Tools/LuaMacro/tests/test-test.lua b/Tools/LuaMacro/tests/test-test.lua new file mode 100644 index 0000000..42f7860 --- /dev/null +++ b/Tools/LuaMacro/tests/test-test.lua @@ -0,0 +1,50 @@ +require_ 'assert' + +-- can compare table values as well +assert_ 2 == 2 +assert_ print == print +assert_ {one=1,two=2} == {two=2,one=1} + +assert_ 'hello' matches '^hell' +assert_ 2 > 1 + +--assert_ 3 < 2 -- quite wrong! + +-- if the first expression returns multiple values, then +-- the second can match this with parentheses + +function two() return 40,2 end + +assert_ two() == (40,2) + +function three() return {1,2},nil,'three' end + +assert_ three() == ({1,2},nil,'three') + +-- 'throws' only succeeds if the expression did actually raise an error, +-- and the error string does match the error message. + +function bad() error 'something bad!' end + +assert_ bad() throws "something bad!" + +a = nil + +assert_ a.x throws "attempt to index global 'a'" + +-- can of course redefine assert_... +def_ assert assert_ + +-- This is an experimental feature, which matches two numbers up to the +-- precision supplied in the second number. This only happens if the test +-- number has a fractional part, and the number must be explicitly +-- be in %f formaat. +assert 3.1412 == 3.14 +assert 2302.24432 == 2302.2 +assert 100 == 100 +assert 1.1e-3 == 0.001 + + + + + diff --git a/Tools/LuaMacro/tests/test-try.lua b/Tools/LuaMacro/tests/test-try.lua new file mode 100644 index 0000000..cfd68a4 --- /dev/null +++ b/Tools/LuaMacro/tests/test-try.lua @@ -0,0 +1,52 @@ +require_ 'macro.try'
+local check
+try
+ try
+ if arg[1] then error('throw!') end
+ except(err)
+ print('shd be throw',err)
+ end
+ a.x = 0
+except(e)
+ check = e
+end
+
+-- the truly tricky case here is the plain return, since we need to distinguish
+-- it from merely leaving the protected block.
+function testtry(n)
+ try
+ if n == 0 then return 'cool'
+ elseif n == 1 then return 'cool',42
+ elseif n == 2 then return --aha
+ elseif n == 3 then
+ error('throw baby!')
+ end
+ except(msg)
+ return nil,msg
+ end
+ return 42,'answer'
+end
+
+function match (x,y)
+ local ok
+ if type(x) == 'string' and type(y) == 'string' then
+ ok = y:find(x)
+ else
+ ok = x == y
+ end
+ if not ok then print('mismatch',x,y) end
+ return ok
+end
+
+function assert2 (x1,x2,y1,y2)
+ assert(match(x1,y1) and match(x2,y2))
+end
+
+assert(match("attempt to index global 'a' %(a nil value%)$",check))
+assert2('cool',nil,testtry(0))
+assert2('cool',42,testtry(1))
+assert2(42,'answer',testtry(2))
+assert2(nil,'throw baby!$',testtry(3))
+assert2(42,'answer',testtry(4))
+
+
diff --git a/Tools/LuaMacro/tests/test-with.lua b/Tools/LuaMacro/tests/test-with.lua new file mode 100644 index 0000000..ac5d0fe --- /dev/null +++ b/Tools/LuaMacro/tests/test-with.lua @@ -0,0 +1,18 @@ +require_ 'macro.with'
+
+aLongTableName = {}
+with aLongTableName do
+ .a = 1
+ .b = {{x=1},{x=2}}
+ .c = {f = 2}
+ print(.a,.c.f,.b[1].x)
+end
+
+def_ @ return
+def_ F function
+
+F f(x) @ x+1 end
+
+print(f(10))
+
+
diff --git a/Tools/LuaMacro/tests/test.inc b/Tools/LuaMacro/tests/test.inc new file mode 100644 index 0000000..4276342 --- /dev/null +++ b/Tools/LuaMacro/tests/test.inc @@ -0,0 +1,3 @@ +print 'hello'
+print 'dolly'
+local answer = 42
diff --git a/Tools/LuaMacro/tests/tests.bat b/Tools/LuaMacro/tests/tests.bat new file mode 100644 index 0000000..f0ff583 --- /dev/null +++ b/Tools/LuaMacro/tests/tests.bat @@ -0,0 +1 @@ +for %%p in (dollar,lambda,try,block,forall,scope,do,const) do luam test-%%p.lua
diff --git a/Tools/LuaMacro/tests/tests.lua b/Tools/LuaMacro/tests/tests.lua new file mode 100644 index 0000000..865c928 --- /dev/null +++ b/Tools/LuaMacro/tests/tests.lua @@ -0,0 +1,27 @@ +require_ 'macro.forall' +require_ 'qw' +local function execute (name) + local file = 'test-'..name..'.lua' + print('executing '..file) + os.execute('luam '..file) +end +forall name in qw(dollar lambda try block scope do const rawhash include test) do + execute (name) +end + +if pcall(require,'pl') then + execute 'list' +end + +local function exec (cmd) + print (cmd) + os.execute(cmd) +end + +exec 'luam -lcskin test-cskin.lua' +exec 'luam test-atm.lua' +exec 'luam -VA test-atm.lua' +exec 'set P=1 && luam test-atm.lua' +exec 'set P=1 && luam -VA test-atm.lua' + + diff --git a/Tools/LuaMacro/tests/winapi.lc b/Tools/LuaMacro/tests/winapi.lc new file mode 100644 index 0000000..723a91c --- /dev/null +++ b/Tools/LuaMacro/tests/winapi.lc @@ -0,0 +1,210 @@ +#define WINDOWS_LEAN_AND_MEAN
+#include <windows.h>
+#include <string.h>
+
+#define eq(s1,s2) (strcmp(s1,s2)==0)
+
+#define WBUFF 2048
+#define MAX_SHOW 100
+
+module "winapi" {
+
+class window {
+ HWND hwnd;
+
+ constructor (HWND h) {
+ this->hwnd = h;
+ }
+
+ static lua_State *sL;
+
+ static BOOL enum_callback(HWND hwnd,LPARAM data) {
+ int ref = (int)data;
+ lua_rawgeti(sL,LUA_REGISTRYINDEX,ref);
+ push_new_window(sL,hwnd);
+ lua_call(sL,1,0);
+ return TRUE;
+ }
+
+ def handle() {
+ lua_pushinteger(L,(int)this->hwnd);
+ return 1;
+ }
+
+ static char buff[WBUFF];
+
+ def get_text() {
+ GetWindowText(this->hwnd,buff,sizeof(buff));
+ lua_pushstring(L,buff);
+ return 1;
+ }
+
+ def show(Int flags = SW_SHOW) {
+ ShowWindow(this->hwnd,flags);
+ return 0;
+ }
+
+ def get_position() {
+ RECT rect;
+ GetWindowRect(this->hwnd,&rect);
+ lua_pushinteger(L,rect.left);
+ lua_pushinteger(L,rect.top);
+ return 2;
+ }
+
+ def get_bounds() {
+ RECT rect;
+ GetWindowRect(this->hwnd,&rect);
+ lua_pushinteger(L,rect.right - rect.left);
+ lua_pushinteger(L,rect.bottom - rect.top);
+ return 2;
+ }
+
+ def is_visible() {
+ lua_pushboolean(L,IsWindowVisible(this->hwnd));
+ return 1;
+ }
+
+ def destroy () {
+ DestroyWindow(this->hwnd);
+ return 0;
+ }
+
+ def resize(Int x0, Int y0, Int w, Int h) {
+ MoveWindow(this->hwnd,x0,y0,w,h,TRUE);
+ return 0;
+ }
+
+ def send_message(Int msg, Int wparam, Int lparam) {
+ SendMessage(this->hwnd,msg,wparam,lparam);
+ }
+
+ def enum_children(Value callback) {
+ int ref;
+ sL = L;
+ lua_pushvalue(L,callback);
+ ref = luaL_ref(L,LUA_REGISTRYINDEX);
+ EnumChildWindows(this->hwnd,&enum_callback,ref);
+ luaL_unref(L,LUA_REGISTRYINDEX,ref);
+ return 0;
+ }
+
+ def get_parent() {
+ push_new_window(L,GetParent(this->hwnd));
+ return 1;
+ }
+
+ def get_module_filename() {
+ int sz = GetWindowModuleFileName(this->hwnd,buff,sizeof(buff));
+ buff[sz] = '\0';
+ lua_pushstring(L,buff);
+ return 1;
+ }
+
+ def __tostring() {
+ GetWindowText(this->hwnd,buff,sizeof(buff));
+ if (strlen(buff) > MAX_SHOW) {
+ strcpy(buff+MAX_SHOW,"...");
+ }
+ lua_pushstring(L,buff);
+ return 1;
+ }
+
+ def __eq(window other) {
+ lua_pushboolean(L,this->hwnd == other->hwnd);
+ return 1;
+ }
+
+}
+
+def find_window(Str cname, Str wname) {
+ HWND hwnd;
+ if (eq(cname,"")) {
+ cname = NULL;
+ }
+ hwnd = FindWindow(cname,wname);
+ push_new_window(L,hwnd);
+ return 1;
+}
+
+def active_window() {
+ push_new_window(L, GetActiveWindow());
+ return 1;
+}
+
+def desktop_window() {
+ push_new_window(L, GetDesktopWindow());
+ return 1;
+}
+
+def enum_windows(Value callback) {
+ int ref;
+ sL = L;
+ lua_pushvalue(L,callback);
+ ref = luaL_ref(L,LUA_REGISTRYINDEX);
+ EnumWindows(&enum_callback,ref);
+ luaL_unref(L,LUA_REGISTRYINDEX,ref);
+ return 0;
+}
+
+def tile_windows(window parent, Boolean horiz, Value kids, Value bounds) {
+ RECT rt;
+ HWND *kids_arr;
+ int i,n_kids;
+ LPRECT lpRect = NULL;
+ if (! lua_isnoneornil(L,bounds)) {
+ lua_pushvalue(L,bounds);
+ Int_get(rt.left,"left");
+ Int_get(rt.top,"top");
+ Int_get(rt.right,"right");
+ Int_get(rt.bottom,"bottom");
+ lua_pop(L,1);
+ }
+ n_kids = lua_objlen(L,kids);
+ kids_arr = (HWND *)malloc(sizeof(HWND)*n_kids);
+ for (i = 0; i < n_kids; ++i) {
+ window *w;
+ lua_rawgeti(L,kids,i+1);
+ w = window_arg(L,-1);
+ kids_arr[i] = w->hwnd;
+ }
+ TileWindows(parent->hwnd,horiz ? MDITILE_HORIZONTAL : MDITILE_VERTICAL, lpRect, n_kids, kids_arr);
+ free(kids_arr);
+ return 0;
+}
+
+def shell_exec(StrNil verb, Str file, StrNil parms, StrNil dir, Int show=SW_SHOWNORMAL) {
+ int res = (int)ShellExecute(NULL,verb,file,parms,dir,show);
+ if (res > 32) {
+ lua_pushboolean(L,1);
+ return 1;
+ } else {
+ const char *msg;
+ switch(res) {
+ #define check_err(NAME) case NAME: msg = #NAME; break;
+ check_err(ERROR_FILE_NOT_FOUND);
+ check_err(ERROR_PATH_NOT_FOUND);
+ check_err(ERROR_BAD_FORMAT);
+ check_err(SE_ERR_ACCESSDENIED);
+ check_err(SE_ERR_ASSOCINCOMPLETE);
+ check_err(SE_ERR_DLLNOTFOUND);
+ check_err(SE_ERR_NOASSOC);
+ check_err(SE_ERR_OOM);
+ check_err(SE_ERR_SHARE);
+ default: msg = "unknown error, probably DDE";
+ #undef check_err
+ }
+ lua_pushnil(L);
+ lua_pushstring(L,msg);
+ return 2;
+ }
+}
+
+constants {
+ SW_HIDE,
+ SW_MAXIMIZE,
+ SW_MINIMIZE,
+ SW_SHOWNORMAL
+}
+
+}
|