Lunatic translator: rework how composites are passed around.

git-svn-id: https://svn.eduke32.com/eduke32@3226 1a8010ca-5511-0410-912e-c29ae57300e0
This commit is contained in:
helixhorned 2012-11-25 13:18:46 +00:00
parent cff452d814
commit 8293e72a95
4 changed files with 147 additions and 99 deletions

View file

@ -7,7 +7,6 @@ local bit = require("bit")
local setmetatable = setmetatable local setmetatable = setmetatable
local assert = assert
local error = error local error = error
local type = type local type = type
@ -31,11 +30,15 @@ local function check_name(name, what, errlev)
end end
local function action_or_move(what, numargs, tab, name, ...) local function action_or_move(what, numargs, tab, name, ...)
assert(lastid[what] > -(2^31)) if (lastid[what] <= -(2^31)) then
error("Too many "..what.."s defined", 3);
end
check_name(name, what, 3) check_name(name, what, 3)
local args = {...} local args = {...}
assert(#args <= numargs) if (#args > numargs) then
error("Too many arguments passed to "..what, 3)
end
for i=1,#args do for i=1,#args do
local n = args[i] local n = args[i]
@ -79,11 +82,13 @@ local function get_action_or_move(what, val, argi)
end end
-- TODO: literal number actions/moves? -- TODO: literal number actions/moves?
error("bad argument #"..argi.." to ai: must be string or "..what) error("bad argument #"..argi.." to ai: must be string or "..what, 3)
end end
function ai(name, action, move, flags) function ai(name, action, move, flags)
assert(lastid.ai > -(2^31)) if (lastid.ai <= -(2^31)) then
error("Too many AIs defined", 2);
end
check_name(name, "ai", 2) check_name(name, "ai", 2)
lastid.ai = lastid.ai-1 lastid.ai = lastid.ai-1
@ -108,7 +113,7 @@ end
function rotatesprite(x, y, zoom, ang, tilenum, shade, pal, orientation, function rotatesprite(x, y, zoom, ang, tilenum, shade, pal, orientation,
cx1, cy1, cx2, cy2) cx1, cy1, cx2, cy2)
if (type(tilenum) ~= "number" or not (tilenum >= 0 and tilenum < ffiC.MAXTILES)) then if (type(tilenum) ~= "number" or not (tilenum >= 0 and tilenum < ffiC.MAXTILES)) then
error("bad argument #5 to rotatesprite: must be number in [0.."..ffiC.MAXTILES.."]") error("bad argument #5 to rotatesprite: must be number in [0.."..ffiC.MAXTILES.."]", 2)
end end
ffiC.rotatesprite(65536*x, 65536*y, zoom, ang, tilenum, shade, pal, bit.bor(2,orientation), ffiC.rotatesprite(65536*x, 65536*y, zoom, ang, tilenum, shade, pal, bit.bor(2,orientation),

View file

@ -450,6 +450,7 @@ end
-- declares struct action and struct move, and their ID-wrapped types -- declares struct action and struct move, and their ID-wrapped types
-- con_action_t and con_move_t -- con_action_t and con_move_t
local con = require("control") local con = require("control")
local MV, AC, AI = con.MV, con.AC, con.AI
-- All-zero action and move -- All-zero action and move
local nullac, nullmv = ffi.new("const struct action"), ffi.new("const struct move") local nullac, nullmv = ffi.new("const struct action"), ffi.new("const struct move")
@ -474,6 +475,11 @@ local actor_mt = {
-- action -- action
set_action = function(a, act) set_action = function(a, act)
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(act)=="string") then
act = AC[act];
end
-- TODO: disallow passing the FFI types altogether, in favor of
-- strings (also move, ai)?
if (ffi.istype(con_action_ct, act)) then if (ffi.istype(con_action_ct, act)) then
a.t_data[4] = act.id a.t_data[4] = act.id
a.ac = act.ac a.ac = act.ac
@ -489,6 +495,9 @@ local actor_mt = {
has_action = function(a, act) has_action = function(a, act)
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(act)=="string") then
act = AC[act];
end
if (ffi.istype(con_action_ct, act)) then if (ffi.istype(con_action_ct, act)) then
return (a.t_data[4]==act.id) return (a.t_data[4]==act.id)
else else
@ -518,6 +527,9 @@ local actor_mt = {
-- move -- move
set_move = function(a, mov, movflags) set_move = function(a, mov, movflags)
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(mov)=="string") then
mov = MV[mov];
end
if (ffi.istype(con_move_ct, mov)) then if (ffi.istype(con_move_ct, mov)) then
a.t_data[1] = mov.id a.t_data[1] = mov.id
a.mv = mov.mv a.mv = mov.mv
@ -536,6 +548,9 @@ local actor_mt = {
has_move = function(a, mov) has_move = function(a, mov)
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(mov)=="string") then
mov = MV[mov];
end
if (ffi.istype(con_move_ct, mov)) then if (ffi.istype(con_move_ct, mov)) then
return (a.t_data[1]==mov.id) return (a.t_data[1]==mov.id)
else else
@ -549,6 +564,9 @@ local actor_mt = {
local oa = a local oa = a
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(mov)=="string") then
ai = AI[ai];
end
-- TODO: literal number AIs? -- TODO: literal number AIs?
if (not ffi.istype(con_ai_ct, ai)) then if (not ffi.istype(con_ai_ct, ai)) then
error("bad argument: expected ai", 2) error("bad argument: expected ai", 2)
@ -566,6 +584,9 @@ local actor_mt = {
has_ai = function(a, ai) has_ai = function(a, ai)
a = ffi.cast(actor_ptr_ct, a) a = ffi.cast(actor_ptr_ct, a)
if (type(mov)=="string") then
ai = AI[ai];
end
if (ffi.istype(con_ai_ct, ai)) then if (ffi.istype(con_ai_ct, ai)) then
return (a.t_data[5]==ai.id) return (a.t_data[5]==ai.id)
else else

View file

@ -65,7 +65,8 @@ local g_loadactor_code = {} -- [actornum]=gencode_table
local function getlinecol(pos) end -- fwd-decl local function getlinecol(pos) end -- fwd-decl
local function reset_codegen() local function reset_codegen()
g_file_code, g_curcode = {}, nil g_file_code = {}
g_curcode = nil
g_actor_code, g_event_code, g_loadactor_code = {}, {}, {} g_actor_code, g_event_code, g_loadactor_code = {}, {}, {}
end end
@ -82,7 +83,7 @@ local function on_actor_end(usertype, tsamm, codetab)
local tilenum = tsamm[1] local tilenum = tsamm[1]
-- usertype is non-nil only for 'useractor' -- usertype is non-nil only for 'useractor'
addcodef("gameactor(%d,\nfunction(actori, playeri, dist)", tilenum) addcodef("gameactor(%d, function(_aci, _pli, _dist)", tilenum)
g_actor_code[tilenum] = codetab g_actor_code[tilenum] = codetab
addcode(codetab) addcode(codetab)
@ -136,35 +137,37 @@ local function parse_number(pos, numstr)
end end
local LABEL = { MOVE=2, AI=3, ACTION=5, [2]="move", [3]="ai", [5]="action" } -- Mapping of various "define" types to the respective number of members and
-- vice versa
local LABEL = { MOVE=2, AI=3, ACTION=5, [2]="move", [3]="ai", [5]="action",
NUMBER=1, [1]="number" }
local MOVE_NO = {0,0} -- Table names in the 'con' module
local ACTION_NO = {0,0,0,0,0} --local LABEL_TABNAME = { [2]="MV", [3]="AI", [5]="AC" }
local LABEL_NO = { [2]=MOVE_NO, [3]={ACTION_NO, MOVE_NO, 0}, [5]=ACTION_NO } -- Function names in the 'con' module
local LABEL_FUNCNAME = { [2]="move", [3]="ai", [5]="action" }
-- will contain: local g_labeldef = {} -- Lua numbers for numbers, strings for composites
-- * scalar numbers: `define'd values local g_labeltype = {}
-- * tables of length 2, 3, 5: move, ai, action definitions (respectively)
-- - move: { hvel <num>, vvel <num> }
-- - ai: { action <label str>, move <label str, or scalar 0 or 1>, flags <num> }
-- - action: { startframe, numframes, viewtype, incval, delay } (all <num>)
-- TODO: IDs for comparison with if*
local g_labeldef = {}
local TEMP_numlookups = {} local TEMP_numlookups = {}
local function reset_labels() local function reset_labels()
TEMP_numlookups = {} TEMP_numlookups = {}
g_labeldef = { NO=0 } -- NO is also a valid `move', `ai' or `action'
-- NO is also a valid `move', `ai' or `action', but they are handled
-- separately in lookup_composite().
g_labeldef = { NO=0 }
g_labeltype = { NO=LABEL.NUMBER }
-- Initialize default defines.
for i=1,#con.labels do for i=1,#con.labels do
for label, val in pairs(con.labels[i]) do for label, val in pairs(con.labels[i]) do
g_labeldef[label] = val g_labeldef[label] = val
g_labeltype[label] = LABEL.NUMBER
end end
end end
end end
-- XXX: error reports give wrong numbers if e.g. happened in "actor" def
-- (since it runs when fully parsed, i.e. at "enda")
local function lookup_defined_label(pos, maybe_minus_str, identifier) local function lookup_defined_label(pos, maybe_minus_str, identifier)
local num = g_labeldef[identifier] local num = g_labeldef[identifier]
@ -173,74 +176,69 @@ local function lookup_defined_label(pos, maybe_minus_str, identifier)
return -inf -- return a number for type cleanness return -inf -- return a number for type cleanness
end end
if (type(num) ~= "number") then if (g_labeltype[identifier] ~= LABEL.NUMBER) then
perrprintf(pos, "label \"%s\" is not a `define'd value", identifier) perrprintf(pos, "label \"%s\" is not a `define'd number", identifier)
return -inf return -inf
end end
assert(type(num)=="number")
return (maybe_minus_str=="" and 1 or -1) * num return (maybe_minus_str=="" and 1 or -1) * num
end end
local function do_define_label(identifier, num) local function do_define_label(identifier, num)
local oldtype = g_labeltype[identifier]
local oldval = g_labeldef[identifier] local oldval = g_labeldef[identifier]
if (oldval) then if (oldval) then
if (type(oldval) == "table") then if (oldtype ~= LABEL.NUMBER) then
errprintf("refusing to overwrite `%s' label \"%s\" with a `define'd value", errprintf("refusing to overwrite `%s' label \"%s\" with a `define'd number",
LABEL[#oldval], identifier) LABEL[oldtype], identifier)
return else
-- con.labels[...]: don't warn for wrong PROJ_ redefinitions
if (oldval ~= num and con.labels[2][identifier]==nil) then
warnprintf("label \"%s\" not redefined with new value %d (old: %d)",
identifier, num, oldval)
end
end end
else
-- con.labels[...]: don't warn for wrong PROJ_ redefinitions -- New definition of a label
if (oldval ~= num and con.labels[2][identifier]==nil) then g_labeldef[identifier] = num
warnprintf("label \"%s\" not redefined with new value %d (old: %d)", g_labeltype[identifier] = LABEL.NUMBER
identifier, num, oldval)
end
return
end end
g_labeldef[identifier] = num
end end
local function check_move_literal(pos, num) local function check_composite_literal(labeltype, pos, num)
if (num~=0 and num~=1) then if (num==0 or num==1) then
perrprintf(pos, "literal `move' number must be either 0 or 1") return (num==0) and "0" or "1"
return MOVE_NO else
perrprintf(pos, "literal `%s' number must be either 0 or 1", LABEL[labeltype])
return "_INVALIT"
end end
-- Both move 0 and 1 have hvel and vvel 0, but they must not compare equal
-- for 'ifmove'. 0.1 will be truncated to 0 when passing to the game.
-- XXX: this is still wrong, we need an ID
return {0.1*num, 0.1*num}
end
local function check_action_or_ai_literal(labeltype, pos, num)
if (num~=0) then
perrprintf(pos, "literal `%s' number must be 0", LABEL[labeltype])
return LABEL_NO[labeltype]
end
return LABEL_NO[labeltype]
end end
local function lookup_composite(labeltype, pos, identifier) local function lookup_composite(labeltype, pos, identifier)
if (identifier=="NO") then if (identifier=="NO") then
-- NO is a special case and is valid for move, ai, action -- NO is a special case and is valid for move, action and ai,
return LABEL_NO[labeltype] -- being the same as passing a literal 0.
return "0"
end end
local val = g_labeldef[identifier] local val = g_labeldef[identifier]
if (val == nil) then if (val == nil) then
perrprintf(pos, "label \"%s\" is not defined", identifier) perrprintf(pos, "label \"%s\" is not defined", identifier)
return LABEL_NO[labeltype] -- return a value of the expected type for cleanness return "_NOTDEF"
elseif (g_labeltype[identifier] ~= labeltype) then
perrprintf(pos, "label \"%s\" is not a%s `%s' value", identifier,
labeltype==LABEL.MOVE and "" or "n", LABEL[labeltype])
return "_WRONGTYPE"
end end
if (type(val)~="table" or #val~=labeltype) then -- Generate a lookup into the control module's move/action/ai defs.
perrprintf(pos, "label \"%s\" is not a%s `%s' value", identifier, -- val = string.format("_con.%s[%q]", LABEL_TABNAME[labeltype], identifier)
labeltype==LABEL.MOVE and "" or "n", LABEL[labeltype]) -- Generate a quoted identifier name.
return LABEL_NO[labeltype] val = string.format("%q", identifier)
end
if (TEMP_numlookups[identifier]) then if (TEMP_numlookups[identifier]) then
TEMP_numlookups[identifier] = TEMP_numlookups[identifier]+1 TEMP_numlookups[identifier] = TEMP_numlookups[identifier]+1
@ -252,35 +250,49 @@ local function lookup_composite(labeltype, pos, identifier)
end end
local function do_define_composite(labeltype, identifier, ...) local function do_define_composite(labeltype, identifier, ...)
local oldtype = g_labeltype[identifier]
local oldval = g_labeldef[identifier] local oldval = g_labeldef[identifier]
if (oldval) then if (oldval) then
if (type(oldval) ~= "table" or #val~=labeltype) then if (oldtype ~= labeltype) then
errprintf("refusing to overwrite `%s' label \"%s\" with a `%s' value", errprintf("refusing to overwrite `%s' label \"%s\" with a `%s' value",
type(oldval)=="number" and "define" or LABEL[#oldval], LABEL[oldtype], identifier, LABEL[labeltype])
identifier, LABEL[labeltype]) else
return warnprintf("duplicate `%s' definition of \"%s\" ignored",
LABEL[labeltype], identifier)
end end
warnprintf("duplicate `%s' definition of \"%s\" ignored",
LABEL[labeltype], identifier)
return return
end end
local val = {...} -- Fill up omitted arguments with zeros.
for i=#val+1,labeltype do local isai = (labeltype == LABEL.AI)
val[i] = LABEL_NO[labeltype][i] local args = {...}
for i=#args+1,labeltype do
-- passing nil to con.ai will make the action/move the null one
args[i] = (isai and i<=2) and "nil" or 0
end end
if (labeltype == LABEL.AI) then if (isai) then
assert(type(args[1])=="string")
assert(type(args[2])=="string")
-- OR together the flags -- OR together the flags
for i=#val,LABEL.AI+1, -1 do for i=#args,LABEL.AI+1, -1 do
val[LABEL.AI] = bit.bor(val[LABEL.AI], val[i]) -- TODO: check?
val[i] = nil args[LABEL.AI] = bit.bor(args[LABEL.AI], args[i])
args[i] = nil
end end
end end
g_labeldef[identifier] = val -- Make a string out of that.
for i=1+(isai and 2 or 0),#args do
args[i] = string.format("%d", args[i])
end
addcodef("_con.%s(%q,%s)\n", LABEL_FUNCNAME[labeltype], identifier, table.concat(args, ","))
g_labeldef[identifier] = ""
g_labeltype[identifier] = labeltype
end end
@ -597,6 +609,9 @@ local Co = {
gamearray = cmd(I,D), gamearray = cmd(I,D),
--- 5. Top level commands that are also run-time commands --- 5. Top level commands that are also run-time commands
move = sp1 * t_identifier * (sp1 * t_define)^-2 / -- hvel, vvel
function(...) do_define_composite(LABEL.MOVE, ...) end,
-- startframe, numframes, viewtype, incval, delay: -- startframe, numframes, viewtype, incval, delay:
action = sp1 * t_identifier * (sp1 * t_define)^-5 / action = sp1 * t_identifier * (sp1 * t_define)^-5 /
function(...) do_define_composite(LABEL.ACTION, ...) end, function(...) do_define_composite(LABEL.ACTION, ...) end,
@ -607,9 +622,6 @@ local Co = {
)^-1 / )^-1 /
function(...) do_define_composite(LABEL.AI, ...) end, function(...) do_define_composite(LABEL.AI, ...) end,
move = sp1 * t_identifier * (sp1 * t_define)^-2 / -- hvel, vvel
function(...) do_define_composite(LABEL.MOVE, ...) end,
--- 6. Deprecated TLCs --- 6. Deprecated TLCs
betaname = newline_term_string, betaname = newline_term_string,
enhanced = cmd(D), enhanced = cmd(D),
@ -736,22 +748,23 @@ local Ci = {
getincangle = cmd(W,R,R), getincangle = cmd(W,R,R),
--- 3. Actors --- 3. Actors
-- These three need more attention (different kind of labels;
-- 'move' additionally may accept 0 or 1):
action = cmd(AC) / action = cmd(AC) /
function(q) return "ACTION("..(q[1] or "nil")..")" end, --TEMP function(str) return string.format("actor[_aci]:set_action(%s)", str) end,
ai = cmd(AI), ai = cmd(AI) /
move = sp1 * t_move * (sp1 * t_define)^0, function(str) return string.format("actor[_aci]:set_ai(%s)", str) end,
-- TODO: move's flags
move = sp1 * t_move * (sp1 * t_define)^0 /
function(str, ...) return string.format("actor[_aci]:set_move(%s)", str) end,
cactor = cmd(D) / cactor = cmd(D) /
"sprite[actori].tilenum=%1", "sprite[_aci].tilenum=%1",
count = cmd(D), count = cmd(D),
cstator = cmd(D), cstator = cmd(D),
cstat = cmd(D), cstat = cmd(D),
clipdist = cmd(D), clipdist = cmd(D),
sizeto = cmd(D,D), sizeto = cmd(D,D),
sizeat = cmd(D,D) / sizeat = cmd(D,D) /
"sprite[actori].xrepeat, sprite[actori].yrepeat = %1, %2", "sprite[_aci].xrepeat, sprite[_aci].yrepeat = %1, %2",
strength = cmd(D), strength = cmd(D),
addstrength = cmd(D), addstrength = cmd(D),
spritepal = cmd(D), spritepal = cmd(D),
@ -1089,6 +1102,7 @@ local function bsearch(tab, searchelt)
end end
function getlinecol(pos) -- local function getlinecol(pos) -- local
assert(type(pos)=="number")
local line = bsearch(g_newlineidxs, pos) local line = bsearch(g_newlineidxs, pos)
assert(line and g_newlineidxs[line]<=pos and pos<g_newlineidxs[line+1]) assert(line and g_newlineidxs[line]<=pos and pos<g_newlineidxs[line+1])
local col = pos-g_newlineidxs[line] local col = pos-g_newlineidxs[line]
@ -1320,15 +1334,15 @@ local Grammar = Pat{
t_move = t_move =
POS()*t_identifier / function(...) return lookup_composite(LABEL.MOVE, ...) end + POS()*t_identifier / function(...) return lookup_composite(LABEL.MOVE, ...) end +
POS()*t_number / check_move_literal, POS()*t_number / function(...) return check_composite_literal(LABEL.MOVE, ...) end,
t_ai = t_ai =
POS()*t_identifier / function(...) return lookup_composite(LABEL.AI, ...) end + POS()*t_identifier / function(...) return lookup_composite(LABEL.AI, ...) end +
POS()*t_number / function(...) return check_action_or_ai_literal(LABEL.AI, ...) end, POS()*t_number / function(...) return check_composite_literal(LABEL.AI, ...) end,
t_action = t_action =
POS()*t_identifier / function(...) return lookup_composite(LABEL.ACTION, ...) end + POS()*t_identifier / function(...) return lookup_composite(LABEL.ACTION, ...) end +
POS()*t_number / function(...) return check_action_or_ai_literal(LABEL.ACTION, ...) end, POS()*t_number / function(...) return check_composite_literal(LABEL.ACTION, ...) end,
t_arrayexp = t_identifier * arraypat * memberpat^-1, t_arrayexp = t_identifier * arraypat * memberpat^-1,
@ -1420,7 +1434,7 @@ function parse(contents) -- local
local curcode = g_curcode local curcode = g_curcode
g_ifseqlevel = 0 g_ifseqlevel = 0
g_curcode = {} g_curcode = { "local _con=require'con'\n" }
g_file_code[g_filename] = g_curcode g_file_code[g_filename] = g_curcode
-- set up new state -- set up new state
@ -1496,6 +1510,8 @@ if (not _EDUKE32_LUNATIC) then
-- NOTE: xpcall isn't useful here since the traceback won't give us -- NOTE: xpcall isn't useful here since the traceback won't give us
-- anything inner to the lpeg.match call -- anything inner to the lpeg.match call
local ok, msg = pcall(do_include_file, g_directory, filename) local ok, msg = pcall(do_include_file, g_directory, filename)
-- ^v Swap commenting (comment top, uncomment bottom line) to get backtraces
-- local ok, msg = true, do_include_file(g_directory, filename)
if (not ok) then if (not ok) then
if (g_lastkwpos ~= nil) then if (g_lastkwpos ~= nil) then
@ -1517,10 +1533,11 @@ if (not _EDUKE32_LUNATIC) then
printf("avg. lookups: %f (%d %d %d)", numl/n, ll[1],ll[2],ll[3]) printf("avg. lookups: %f (%d %d %d)", numl/n, ll[1],ll[2],ll[3])
--[[ --[[
local file = io.stdout
for filename,codetab in pairs(g_file_code) do for filename,codetab in pairs(g_file_code) do
io.stderr:write(string.format("-- GENERATED CODE (%s):\n", filename)) file:write(string.format("-- GENERATED CODE (%s):\n", filename))
io.stderr:write(table.concat(flatten_codetab(codetab), "\n")) file:write(table.concat(flatten_codetab(codetab), "\n"))
io.stderr:write("\n") file:write("\n")
end end
--]] --]]
end end

View file

@ -236,7 +236,12 @@ local con = require("con")
local AC, MV = con.AC, con.MV local AC, MV = con.AC, con.MV
con.action("TROOPFLINTCH", 50, 1, 1, 1, 6) con.action("TROOPFLINTCH", 50, 1, 1, 1, 6)
con.move("SHRUNKVELS", 32) con.move("SHRUNKVELS", 32)
con.ai("AITEMP", "TROOPFLINTCH", MV.SHRUNKVELS, 0) -- TODO: test con.ai("AITEMP", AC.TROOPFLINTCH, MV.SHRUNKVELS, 0) -- TODO: test
-- This should work as well. In fact, it's exactly the same, but I prefer the
-- above version for clarity. NOTE: we'll need to think whether it's OK to
-- redefine composites (moves/actions/ais) during gameplay (probably not).
-- Or will we allow only one definition per label ever?
con.ai("AITEMP", "TROOPFLINTCH", "SHRUNKVELS", 0)
gameactor(1680, -- LIZTROOP gameactor(1680, -- LIZTROOP
function(i, playeri, dist) function(i, playeri, dist)
@ -257,8 +262,8 @@ gameactor(1680, -- LIZTROOP
if (dist < 4096) then if (dist < 4096) then
-- Duke Vader / Anakin Nukewalker? -- Duke Vader / Anakin Nukewalker?
actor[i]:set_action(AC.TROOPFLINTCH) actor[i]:set_action("TROOPFLINTCH")
actor[i]:set_move(MV.SHRUNKVELS) actor[i]:set_move("SHRUNKVELS")
end end
end end
) )