raze-gles/polymer/eduke32/source/lunatic/lunacon.lua

1693 lines
51 KiB
Lua
Raw Normal View History

-- LunaCON CON to Lunatic translator
-- requires LPeg, http://www.inf.puc-rio.br/~roberto/lpeg/lpeg.html
local lpeg = require("lpeg")
if (not _EDUKE32_LUNATIC) then
require("strict")
end
-- I think that the "too many pending calls/choices" is unavoidable in general.
-- This limit is of course still arbitrary, but writing long if/else cascades
-- in CON isn't pretty either (though sometimes necessary because nested switches
-- don't work?)
-- See also: http://lua-users.org/lists/lua-l/2010-03/msg00086.html
lpeg.setmaxstack(1024);
local Pat, Set, Range, Var = lpeg.P, lpeg.S, lpeg.R, lpeg.V
local POS = lpeg.Cp
---- All keywords pattern -- needed for CON syntax
local conl = require("con_lang")
local function match_until(matchsp, untilsp) -- (!untilsp matchsp)* in PEG
-- sp: string or pattern
return (matchsp - Pat(untilsp))^0
end
local format = string.format
local function printf(fmt, ...)
print(format(fmt, ...))
end
---=== semantic action functions ===---
local inf = 1/0
local NaN = 0/0
-- Last keyword position, for error diagnosis.
local g_lastkwpos = nil
local g_lastkw = nil
local g_badids = {} -- maps bad id strings to 'true'
local g_recurslevel = -1 -- 0: base CON file, >0 included
local g_filename = "???"
local g_directory = "" -- with trailing slash if not empty
local g_numerrors = 0
-- Warning options. Key names are the same as cmdline options, e.g.
-- -Wno-bad-identifier for disabling the "bad identifier" warning.
local g_warn = { ["not-redefined"]=true, ["bad-identifier"]=true, }
-- How many 'if' statements are following immediately each other,
-- needed to cope with CONs dangling-else resolution
local g_ifseqlevel = 0
---=== Code generation ===---
local g_file_code = {} -- a [filename]=gencode_table mapping
local g_curcode = nil -- a table of string pieces or other "gencode" tables
local g_actor_code = {} -- [actornum]=gencode_table
local g_event_code = {} -- [eventnum]=gencode_table
local g_loadactor_code = {} -- [actornum]=gencode_table
local function getlinecol(pos) end -- fwd-decl
local function reset_codegen()
g_file_code = {}
g_curcode = nil
g_actor_code, g_event_code, g_loadactor_code = {}, {}, {}
end
local function addcode(x)
assert(type(x)=="string" or type(x)=="table")
g_curcode[#g_curcode+1] = x
end
local function addcodef(fmt, ...)
addcode(format(fmt, ...))
end
local function on_actor_end(usertype, tsamm, codetab)
-- TODO: strength, action, move, moveflags
local tilenum = tsamm[1]
-- usertype is non-nil only for 'useractor'
addcodef("gameactor(%d, function(_aci, _pli, _dist)", tilenum)
assert(type(codetab)=="table")
g_actor_code[tilenum] = codetab
addcode(codetab)
addcode("end)")
end
local function on_state_end(statename, codetab)
-- TODO: mangle names, make them accessible from other translation units
addcodef("local function %s()", statename)
assert(type(codetab)=="table")
addcode(codetab)
addcode("end")
end
----------
local function linecolstr(pos)
local line, col = getlinecol(pos)
return format("%d:%d", line, col)
end
local function perrprintf(pos, fmt, ...)
printf("%s %s: error: "..fmt, g_filename, linecolstr(pos), ...)
end
local function errprintf(fmt, ...)
if (g_lastkwpos) then
perrprintf(g_lastkwpos, fmt, ...)
else
printf("%s ???: error: "..fmt, g_filename, ...)
end
g_numerrors = g_numerrors+1
end
local function pwarnprintf(pos, fmt, ...)
printf("%s %s: warning: "..fmt, g_filename, linecolstr(pos), ...)
end
local function warnprintf(fmt, ...)
if (g_lastkwpos) then
pwarnprintf(g_lastkwpos, fmt, ...)
else
printf("%s ???: warning: "..fmt, g_filename, ...)
end
end
local function parse_number(pos, numstr)
local num = tonumber(numstr)
if (num==nil or num < -0x80000000 or num > 0xffffffff) then
perrprintf(pos, "number %s out of the range of a 32-bit integer", numstr)
num = NaN
elseif (num >= 0x80000000 and numstr:sub(1,2):lower()~="0x") then
pwarnprintf(pos, "number %s converted to a negative one", numstr)
num = num-(0xffffffff+1)
end
return num
end
-- 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" }
-- Function names in the 'con' module
local LABEL_FUNCNAME = { [2]="move", [3]="ai", [5]="action" }
local g_labeldef = {} -- Lua numbers for numbers, strings for composites
local g_labeltype = {}
local function reset_labels()
-- 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,#conl.labels do
for label, val in pairs(conl.labels[i]) do
g_labeldef[label] = val
g_labeltype[label] = LABEL.NUMBER
end
end
end
local function lookup_defined_label(pos, maybe_minus_str, identifier)
local num = g_labeldef[identifier]
if (num == nil) then
perrprintf(pos, "label \"%s\" is not defined", identifier)
return -inf -- return a number for type cleanness
end
if (g_labeltype[identifier] ~= LABEL.NUMBER) then
perrprintf(pos, "label \"%s\" is not a `define'd number", identifier)
return -inf
end
assert(type(num)=="number")
return (maybe_minus_str=="" and 1 or -1) * num
end
local function do_define_label(identifier, num)
local oldtype = g_labeltype[identifier]
local oldval = g_labeldef[identifier]
if (oldval) then
if (oldtype ~= LABEL.NUMBER) then
errprintf("refusing to overwrite `%s' label \"%s\" with a `define'd number",
LABEL[oldtype], identifier)
else
-- conl.labels[...]: don't warn for wrong PROJ_ redefinitions
if (g_warn["not-redefined"]) then
if (oldval ~= num and conl.labels[2][identifier]==nil) then
warnprintf("label \"%s\" not redefined with new value %d (old: %d)",
identifier, num, oldval)
end
end
end
else
-- New definition of a label
g_labeldef[identifier] = num
g_labeltype[identifier] = LABEL.NUMBER
end
end
local function check_composite_literal(labeltype, pos, num)
if (num==0 or num==1) then
return (num==0) and "0" or "1"
else
perrprintf(pos, "literal `%s' number must be either 0 or 1", LABEL[labeltype])
return "_INVALIT"
end
end
local function lookup_composite(labeltype, pos, identifier)
if (identifier=="NO") then
-- NO is a special case and is valid for move, action and ai,
-- being the same as passing a literal 0.
return "0"
end
local val = g_labeldef[identifier]
if (val == nil) then
perrprintf(pos, "label \"%s\" is not defined", identifier)
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
-- Generate a quoted identifier name.
val = format("%q", identifier)
return val
end
local function do_define_composite(labeltype, identifier, ...)
local oldtype = g_labeltype[identifier]
local oldval = g_labeldef[identifier]
if (oldval) then
if (oldtype ~= labeltype) then
errprintf("refusing to overwrite `%s' label \"%s\" with a `%s' value",
LABEL[oldtype], identifier, LABEL[labeltype])
else
warnprintf("duplicate `%s' definition of \"%s\" ignored",
LABEL[labeltype], identifier)
end
return
end
-- Fill up omitted arguments with zeros.
local isai = (labeltype == LABEL.AI)
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
if (isai) then
assert(type(args[1])=="string")
assert(type(args[2])=="string")
-- OR together the flags
for i=#args,LABEL.AI+1, -1 do
-- TODO: check?
args[LABEL.AI] = bit.bor(args[LABEL.AI], args[i])
args[i] = nil
end
end
-- Make a string out of that.
for i=1+(isai and 2 or 0),#args do
args[i] = format("%d", args[i])
end
addcodef("_con.%s(%q,%s)", LABEL_FUNCNAME[labeltype], identifier, table.concat(args, ","))
g_labeldef[identifier] = ""
g_labeltype[identifier] = labeltype
end
local function parse(contents) end -- fwd-decl
local function do_include_file(dirname, filename) end
local function cmd_include(filename) end
if (_EDUKE32_LUNATIC) then
-- NOT IMPLEMENTED
else
function do_include_file(dirname, filename)
local io = require("io")
local fd, msg = io.open(dirname..filename)
if (fd == nil) then
-- strip up to and including first slash:
filename = string.gsub(filename, "^.-/", "")
fd, msg = io.open(dirname..filename)
if (fd == nil) then
printf("[%d] Fatal error: couldn't open %s", g_recurslevel, msg)
g_numerrors = inf
return
end
end
if (g_file_code[filename] ~= nil) then
printf("[%d] Fatal error: infinite loop including \"%s\"", filename)
g_numerrors = inf
return
end
local contents = fd:read("*all")
fd:close()
if (contents == nil) then
-- maybe that file name turned out to be a directory or other
-- special file accidentally
printf("[%d] Fatal error: couldn't read from \"%s\"",
g_recurslevel, dirname..filename)
g_numerrors = inf
return
end
printf("%s[%d] Parsing file \"%s\"", (g_recurslevel==-1 and "\n---- ") or "",
g_recurslevel+1, dirname..filename);
local oldfilename = g_filename
g_filename = filename
parse(contents)
g_filename = oldfilename
end
function cmd_include(filename)
do_include_file(g_directory, filename)
end
end
--- Per-module game data
local g_data = {}
local EPMUL = conl.MAXLEVELS
local function reset_gamedata()
g_data = {}
-- [EPMUL*ep + lev] = { ptime=<num>, dtime=<num>, fn=<str>, name=<str> }
g_data.level = {}
-- [ep] = <str>
g_data.volname = {}
-- [skillnum] = <str>
g_data.skillname = {}
-- [quotenum] = <str>
g_data.quote = {}
-- table of length 26 or 30 containg numbers
g_data.startup = {}
-- [soundnum] = { fn=<str>, params=<table of length 5> }
g_data.sound = {}
-- [volnum] = <table of length numlevels (<= MAXLEVELS) of <str>>
g_data.music = {}
end
local function cmd_definelevelname(vol, lev, fn, ptstr, dtstr, levname)
if (vol < 0 or vol >= conl.MAXVOLUMES) then
errprintf("volume number exceeds maximum volume count.")
return
end
if (lev < 0 or lev >= conl.MAXLEVELS) then
errprintf("level number exceeds maximum number of levels per episode.")
return
end
-- TODO: Bcorrectfilename(fn)
local function secs(tstr)
local m, s = string.match(tstr, ".+:.+")
m, s = tonumber(m), tonumber(s)
return (m and s) and m*60+s or 0
end
g_data.level[EPMUL*vol+lev] = {
ptime=secs(ptstr), dtime=secs(dtstr), fn=fn, name="/"..levname
}
end
local function cmd_defineskillname(skillnum, name)
if (skillnum < 0 or skillnum >= conl.MAXSKILLS) then
errprintf("volume number is negative or exceeds maximum skill count.")
return
end
g_data.skillname[skillnum] = name:upper()
end
local function cmd_definevolumename(vol, name)
if (vol < 0 or vol >= conl.MAXVOLUMES) then
errprintf("volume number is negative or exceeds maximum volume count.")
return
end
g_data.volname[vol] = name:upper()
end
local function cmd_definequote(qnum, quotestr)
-- have the INT_MAX limit simply for some sanity
if (qnum < 0 or qnum > 0x7fffffff) then
errprintf("quote number is negative or exceeds limit of INT32_MAX.")
return
end
-- strip whitespace from front and back
g_data.quote[qnum] = quotestr:match("^%s*(.*)%s*$")
end
local function cmd_gamestartup(...)
local nums = {...}
if (#nums ~= 26 and #nums ~= 30) then
errprintf("must pass either 26 (1.3D) or 30 (1.5) values")
return
end
g_data.startup = nums -- TODO: sanity-check them
end
local function cmd_definesound(sndnum, fn, ...)
if (sndnum < 0 or sndnum >= conl.MAXSOUNDS) then
errprintf("sound number is or exceeds sound limit of %d", conl.MAXSOUNDS)
return
end
local params = {...} -- TODO: sanity-check them
g_data.sound[sndnum] = { fn=fn, params=params }
end
local function cmd_music(volnum, ...)
if (volnum < 0 or volnum >= conl.MAXVOLUMES+1) then
errprintf("volume number is negative or exceeds maximum volume count+1")
return
end
local filenames = {...}
if (#filenames > conl.MAXLEVELS) then
warnprintf("ignoring extraneous %d music file names", #filenames-conl.MAXLEVELS)
for i=conl.MAXLEVELS+1,#filenames do
filenames[i] = nil
end
end
g_data.music[volnum] = filenames
end
----==== patterns ====----
---- basic ones
-- Windows, *nix and Mac newlines all exist in the wild!
local newline = "\r"*Pat("\n")^-1 + "\n"
local EOF = Pat(-1)
local anychar = Pat(1)
-- comments
local comment = "/*" * match_until(anychar, "*/") * "*/"
local linecomment = "//" * match_until(anychar, newline)
local whitespace = Var("whitespace")
local sp0 = whitespace^0
-- This "WS+" pattern matches EOF too, so that a forgotten newline at EOF is
-- properly handled
local sp1 = whitespace^1 + EOF
local alpha = Range("AZ", "az") -- locale?
local alphanum = alpha + Range("09")
--local alnumtok = alphanum + Set("{}/\\*-_.") -- see isaltok() in gamedef.c
--- basic lexical elements ("tokens")
local t_maybe_minus = (Pat("-") * sp0)^-1;
local t_number = POS() * lpeg.C(
t_maybe_minus * ((Pat("0x") + "0X")*Range("09", "af", "AF")^1 + Range("09")^1)
) / parse_number
-- Valid identifier names are disjunct from keywords!
-- XXX: CON is more permissive with identifier name characters:
local t_identifier = Var("t_identifier")
-- This one matches keywords, too:
local t_identifier_all = Var("t_identifier_all")
local t_define = Var("t_define")
local t_move = Var("t_move")
local t_ai = Var("t_ai")
local t_action = Var("t_action")
-- NOTE: no chance to whitespace and double quotes in filenames:
local t_filename = lpeg.C((anychar-Set(" \t\r\n\""))^1)
local t_newline_term_str = match_until(anychar, newline)
-- new-style inline arrays and structures:
local t_arrayexp = Var("t_arrayexp")
-- defines and constants can take the place of vars that are only read:
-- NOTE: when one of t_identifier+t_define matches, we don't actually know
-- whether it's the right one yet, since their syntax overlaps.
local t_rvar = t_arrayexp + t_identifier + t_define
-- not so with written-to vars:
local t_wvar = t_arrayexp + t_identifier
---- helper patterns / pattern constructing functions
local maybe_quoted_filename = ('"' * t_filename * '"' + t_filename)
-- empty string is handled too; we must not eat the newline then!
local newline_term_string = (#newline + EOF)*lpeg.Cc("")
+ (whitespace-newline)^1 * lpeg.C(t_newline_term_str)
-- (sp1 * t_define) repeated exactly n times
local function n_defines(n) -- works well only for small n
local pat = Pat(true)
for i=1,n do
pat = sp1 * t_define * pat
end
return pat
end
local D, R, W, I, AC, MV, AI = -1, -2, -3, -4, -5, -6, -7
local TOKEN_PATTERN = { [D]=t_define, [R]=t_rvar, [W]=t_wvar, [I]=t_identifier,
[AC]=t_action, [MV]=t_move, [AI]=t_ai }
-- Generic command pattern, types given by varargs.
-- The command name to be matched is attached later.
-- Example:
-- "command" writtenvar readvar def def: gencmd(W,R,D,D)
-- --> sp1 * t_wvar * sp1 * t_rvar * sp1 * t_define * sp1 * t_define
-- "command_with_no_args": gencmd()
-- --> Pat(true)
local function cmd(...)
local pat = Pat(true)
local vartypes = {...}
for i=1,#vartypes do
pat = pat * sp1 * assert(TOKEN_PATTERN[vartypes[i]])
end
return pat
end
local t_time = lpeg.C(alphanum*alphanum^-1*":"*alphanum*alphanum^-1) -- for definelevelname
-- The command names will be attached to the front of the patterns later!
--== Top level CON commands ==--
-- XXX: many of these are also allowed inside actors/states/events in CON.
local Co = {
--- 1. Preprocessor
include = sp1 * maybe_quoted_filename / cmd_include,
includedefault = cmd(),
define = cmd(I,D) / do_define_label,
--- 2. Defines and Meta-Settings
dynamicremap = cmd(),
setcfgname = sp1 * t_filename,
setdefname = sp1 * t_filename,
setgamename = newline_term_string,
precache = cmd(D,D,D),
scriptsize = cmd(D), -- unused
cheatkeys = cmd(D,D),
definecheat = newline_term_string, -- XXX: actually tricker syntax (TS)
definegamefuncname = newline_term_string, -- XXX: TS?
definegametype = n_defines(2) * newline_term_string,
definelevelname = n_defines(2) * sp1 * t_filename * sp1 * t_time * sp1 * t_time *
newline_term_string / cmd_definelevelname,
defineskillname = sp1 * t_define * newline_term_string / cmd_defineskillname,
definevolumename = sp1 * t_define * newline_term_string / cmd_definevolumename,
definequote = sp1 * t_define * newline_term_string / cmd_definequote,
defineprojectile = cmd(D,D,D),
definesound = sp1 * t_define * sp1 * maybe_quoted_filename * n_defines(5) / cmd_definesound,
-- NOTE: gamevar.ogg and the like is OK, too
music = sp1 * t_define * match_until(sp1 * t_filename, sp1 * conl.keyword * sp1) / cmd_music,
--- 3. Game Settings
-- gamestartup has 26/30 fixed defines, depending on 1.3D/1.5 version:
gamestartup = (sp1 * t_define)^26 / cmd_gamestartup,
spritenopal = cmd(D),
spritenoshade = cmd(D),
spritenvg = cmd(D),
spriteshadow = cmd(D),
spriteflags = cmd(D,D), -- also see inner
--- 4. Game Variables / Arrays
gamevar = cmd(I,D,D),
gamearray = cmd(I,D),
--- 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:
action = sp1 * t_identifier * (sp1 * t_define)^-5 /
function(...) do_define_composite(LABEL.ACTION, ...) end,
-- action, move, flags...:
ai = sp1 * t_identifier * (sp1 * t_action *
(sp1 * t_move * (sp1 * t_define)^0)^-1
)^-1 /
function(...) do_define_composite(LABEL.AI, ...) end,
--- 6. Deprecated TLCs
betaname = newline_term_string,
enhanced = cmd(D),
}
--== Run time CON commands ==--
--- 1. Gamevar Operators
local varop = cmd(W,D)
local varvarop = cmd(W,R)
-- Allow nesting... stuff like
-- ifvarl actorvar[sprite[THISACTOR].owner].burning 0
-- is kinda breaking the classic "no array nesting" rules
-- (if there ever were any) and making our life harder else.
local arraypat = sp0 * "[" * sp0 * t_rvar * sp0 * "]"
-- Have to bite the bullet here and list actor/player members with second parameters,
-- even though it's ugly to make it part of the syntax. Also, stuff like
-- actor[xxx].loogiex parm2 x
-- will be wrongly accepted at the parsing stage because we don't discriminate between
-- actor and player (but it will be rejected later).
local parm2memberpat = (Pat("htg_t") + "loogiex" + "loogiey" + "ammo_amount" +
"weaprecs" + "gotweapon" + "pals" + "max_ammo_amount") * sp1 * t_rvar
-- The member name must match keywords, too (_all), because e.g. cstat is a member
-- of sprite[].
local memberpat = sp0 * "." * sp0 * (parm2memberpat + t_identifier_all)
local getstructcmd = -- get<structname>[<idx>].<member> (<parm2>)? <<var>>
-- existence of a second parameter is determined later
-- This is wrong, (sp1 id)? will match (sp1 wvar) if there's no 2nd param:
-- arraypat * memberpat * (sp1 * t_identifier)^-1 * sp1 * t_wvar
arraypat * memberpat * sp1 * (t_rvar * sp1 * t_wvar + t_wvar)
local setstructcmd = -- set<structname>[<idx>].<member> (<parm2>)? <var>
-- existence of a second parameter is determined later
arraypat * memberpat * sp1 * (t_rvar * sp1 * t_rvar + t_rvar)
local getperxvarcmd = -- get<actor/player>var[<idx>].<member> <<var>>
arraypat * memberpat * sp1 * t_wvar
local setperxvarcmd = -- set<actor/player>var[<idx>].<member> <var>
arraypat * memberpat * sp1 * t_rvar
local function ACS(s) return "actor[_aci]"..s end
local function SPS(s) return "sprite[_aci]"..s end
local function PLS(s) return "player[_pli]"..s end
local function handle_palfrom(...)
local v = {...}
return format(PLS":_palfrom(%d,%d,%d,%d)",
v[1] or 0, v[2] or 0, v[3] or 0, v[4] or 0)
end
-- NOTE about prefixes: most is handled by all_alt_pattern(), however commands
-- that have no arguments and that are prefixes of other commands MUST be
-- suffixed with a "* #sp1" pattern.
local Ci = {
-- these can appear anywhere in the script
["break"] = cmd()
/ "do return end", -- TODO: more exact semantics
["return"] = cmd() -- NLCF
/ "_con.longjmp()", -- TODO: test with code from Wiki "return" entry
state = cmd(I)
/ "%1()", -- TODO: mangle names
--- 1. get*, set*
getactor = getstructcmd,
getinput = getstructcmd,
getplayer = getstructcmd,
getprojectile = getstructcmd,
getsector = getstructcmd,
getthisprojectile = getstructcmd,
gettspr = getstructcmd,
-- NOTE: {get,set}userdef is the only struct that can be accessed without
Massive menu input control revamp/cleanup/factor. (added: input.[ch]) New Wii control defaults for the Wii Remote + Nunchuk and the Classic Controller. This includes new code added just so that the Home key brings up the menu in-game, reducing the need for a USB keyboard. On the technical side, raw joystick access (comparable to what is available for keyboard and mouse) is now present in jmact, on the game side. (added: joystick.[ch]) Using this new raw joystick access, I replaced tueidj's hack to map A and B to LMB/RMB and D-Pad Up/Down to the scrollwheel. I made the menus more friendly to mouse and joystick browsing by adding and unifying checks and clears for various buttons and gamefuncs. In fact, the majority of the time spent on this commit was tracking down problems that appeared with the factoring and trying to understand the menu system and the way input checks are precariously executed. In addition, "Press any key or button to continue" now truly means what it says. As a result of incorporating proper raw access into control.c instead of it directly accessing the implementaiton, the program *may* no longer be affected by joystick input when it is out of focus. This follows the pattern set by the mouse, and I think this is a positive change. A small bonus: In the classic/old keyboard preset, the key for Show_Console has been changed from '`' to 'C' because '`' is taken by Quick_Kick. git-svn-id: https://svn.eduke32.com/eduke32@2728 1a8010ca-5511-0410-912e-c29ae57300e0
2012-06-03 16:11:22 +00:00
-- an "array part", e.g. H266MOD has "setuserdef .weaponswitch 0" (space
-- between keyword and "." is mandatory)
getuserdef = (arraypat + sp1) * memberpat * sp1 * (t_rvar * sp1 * t_wvar + t_wvar),
-- getuserdef = getstructcmd,
getwall = getstructcmd,
getactorvar = getperxvarcmd,
getplayervar = getperxvarcmd,
setactor = setstructcmd,
setinput = setstructcmd,
setplayer = setstructcmd,
setprojectile = setstructcmd,
setsector = setstructcmd,
setthisprojectile = setstructcmd,
settspr = setstructcmd,
setuserdef = (arraypat + sp1) * memberpat * sp1 * (t_rvar * sp1 * t_wvar + t_rvar),
-- setuserdef = setstructcmd,
setwall = setstructcmd,
setactorvar = setperxvarcmd,
setplayervar = setperxvarcmd,
setsprite = cmd(R,R,R,R),
setvarvar = varvarop,
addvarvar = varvarop,
subvarvar = varvarop,
mulvarvar = varvarop,
divvarvar = varvarop,
modvarvar = varvarop,
andvarvar = varvarop,
orvarvar = varvarop,
xorvarvar = varvarop,
randvarvar = varvarop,
setvar = varop,
addvar = varop,
subvar = varop,
mulvar = varop,
divvar = varop,
modvar = varop,
andvar = varop,
orvar = varop,
xorvar = varop,
randvar = varop,
shiftvarl = varop,
shiftvarr = varop,
--- 2. Math operations
sqrt = cmd(R,W),
calchypotenuse = cmd(W,R,R),
sin = cmd(W,R),
cos = cmd(W,R),
mulscale = cmd(W,R,R,R),
getangle = cmd(W,R,R),
getincangle = cmd(W,R,R),
--- 3. Actors
action = cmd(AC)
/ ACS":set_action(%1)",
ai = cmd(AI)
/ ACS":set_ai(%1)",
-- TODO: move's flags
move = sp1 * t_move * (sp1 * t_define)^0
/ ACS":set_move(%1)",
cactor = cmd(D)
/ SPS":set_picnum(%1)",
count = cmd(D)
/ ACS":set_count(%1)",
cstator = cmd(D)
/ (SPS".cstat=_bit.bor(%1,"..SPS".cstat)"),
cstat = cmd(D)
/ SPS".cstat=%1",
clipdist = cmd(D)
/ SPS".clipdist=%1",
sizeto = cmd(D,D)
/ "_con._sizeto(_aci)", -- TODO: see control.lua:_sizeto
sizeat = cmd(D,D)
/ (SPS".xrepeat,"..SPS".yrepeat=%1,%2"),
strength = cmd(D)
/ SPS".extra=%1",
addstrength = cmd(D)
/ (SPS".extra="..SPS".extra+%1"),
spritepal = cmd(D),
hitradius = cmd(D,D,D,D,D)
/ "_con._A_RadiusDamage(%1,%2,%3,%4,%5)",
hitradiusvar = cmd(R,R,R,R,R),
-- some commands taking read vars
eshootvar = cmd(R),
espawnvar = cmd(R),
qspawnvar = cmd(R),
eqspawnvar = cmd(R),
operaterespawns = cmd(R),
operatemasterswitches = cmd(R),
checkactivatormotion = cmd(R),
time = cmd(R), -- no-op
inittimer = cmd(R),
lockplayer = cmd(R),
shootvar = cmd(R),
quake = cmd(R),
jump = cmd(R),
cmenu = cmd(R),
soundvar = cmd(R),
globalsoundvar = cmd(R),
stopsoundvar = cmd(R),
soundoncevar = cmd(R),
angoffvar = cmd(R),
checkavailweapon = cmd(R),
checkavailinven = cmd(R),
guniqhudid = cmd(R),
savegamevar = cmd(R),
readgamevar = cmd(R),
userquote = cmd(R),
echo = cmd(R),
starttrackvar = cmd(R),
clearmapstate = cmd(R),
activatecheat = cmd(R),
setgamepalette = cmd(R),
-- some commands taking defines
addammo = cmd(D,D) -- NLCF
/ format("if (%s) then _con.longjmp() end", PLS":addammo(%1,%2)"),
addweapon = cmd(D,D) -- NLCF
/ format("if (%s) then _con.longjmp() end", PLS":addweapon(%1,%2)"),
debris = cmd(D,D)
/ "", -- TODO
addinventory = cmd(D,D)
/ PLS":addinventory(%1,%2)",
guts = cmd(D,D)
/ "", -- TODO
-- cont'd
addkills = cmd(D)
/ (PLS".actors_killed="..PLS".actors_killed+%1;"..ACS".actorstayput=-1"),
addphealth = cmd(D)
/ "", -- TODO
angoff = cmd(D),
debug = cmd(D)
/ "", -- TODO?
endofgame = cmd(D)
/ "_con._endofgame(_pli,%1)",
eqspawn = cmd(D),
espawn = cmd(D),
globalsound = cmd(D)
/ "",
lotsofglass = cmd(D),
mail = cmd(D)
/ "", -- TODO
money = cmd(D)
/ "", -- TODO
paper = cmd(D)
/ "", -- TODO
qspawn = cmd(D),
quote = cmd(D)
/ "", -- TODO
savenn = cmd(D),
save = cmd(D),
sleeptime = cmd(D)
/ ACS".timetosleep=%1",
soundonce = cmd(D),
sound = cmd(D)
/ "", -- TODO: all things audio...
spawn = cmd(D),
stopsound = cmd(D)
/ "",
eshoot = cmd(D),
ezshoot = cmd(R,D),
ezshootvar = cmd(R,R),
shoot = cmd(D)
/ "_con._A_Shoot(_aci, %1)",
zshoot = cmd(R,D),
zshootvar = cmd(R,R),
fall = cmd()
/ "_con._VM_FallSprite(_aci)",
flash = cmd(),
getlastpal = cmd()
/ "_con._getlastpal(_aci)",
insertspriteq = cmd(),
killit = cmd() -- NLCF
/ "_con.killit()",
mikesnd = cmd(),
nullop = cmd()
/ "", -- NOTE: really generate no code
pkick = cmd()
/ "", -- TODO
pstomp = cmd()
/ PLS":pstomp(_aci)",
resetactioncount = cmd()
/ ACS":reset_acount()",
resetcount = cmd()
/ ACS":set_count(0)",
resetplayer = cmd() -- NLCF
/ "if (_con._VM_ResetPlayer2(_pli,_aci)) then _con.longjmp() end",
respawnhitag = cmd()
/ "", -- TODO
tip = cmd()
/ PLS".tipincs=26",
tossweapon = cmd()
/ "", -- TODO
wackplayer = cmd()
/ PLS":wack()",
-- player/sprite searching
findplayer = cmd(W),
findotherplayer = cmd(W),
findnearspritezvar = cmd(D,R,R,W),
findnearspritez = cmd(D,D,D,W),
findnearsprite3dvar = cmd(D,R,W),
findnearsprite3d = cmd(D,D,W),
findnearspritevar = cmd(D,R,W),
findnearsprite = cmd(D,D,W),
findnearactorzvar = cmd(D,R,R,W),
findnearactorz = cmd(D,D,D,W),
findnearactor3dvar = cmd(D,R,W),
findnearactor3d = cmd(D,D,W),
findnearactorvar = cmd(D,R,W),
findnearactor = cmd(D,D,W),
-- quotes
qsprintf = sp1 * t_rvar * sp1 * t_rvar * (sp1 * t_rvar)^-32,
qgetsysstr = cmd(R,R),
qstrcat = cmd(R,R),
qstrcpy = cmd(R,R),
qstrlen = cmd(R,R),
qstrncat = cmd(R,R),
qsubstr = cmd(R,R),
-- array stuff
copy = sp1 * t_identifier * arraypat * sp1 * t_identifier * arraypat * sp1 * t_rvar,
setarray = sp1 * t_identifier * arraypat * sp1 * t_rvar,
activatebysector = cmd(R,R),
addlogvar = cmd(R),
addlog = cmd() * #sp1,
addweaponvar = cmd(R,R), -- exec SPECIAL HANDLING!
cansee = cmd(R,R,R,R,R,R,R,R,W),
canseespr = cmd(R,R,W),
changespritesect = cmd(R,R),
changespritestat = cmd(R,R),
clipmove = cmd(W,W,W,R,W,R,R,R,R,R,R),
clipmovenoslide = cmd(W,W,W,R,W,R,R,R,R,R,R),
displayrand = cmd(W),
displayrandvar = cmd(W,D),
displayrandvarvar = cmd(W,R),
dist = cmd(W,R,R),
dragpoint = cmd(R,R,R),
hitscan = cmd(R,R,R,R,R,R,R,W,W,W,W,W,W,R), -- 7R 6W 1R
-- screen text and numbers display
gametext = cmd(R,R,R,R,R,R,R,R,R,R,R), -- 11 R
gametextz = cmd(R,R,R,R,R,R,R,R,R,R,R,R), -- 12 R
digitalnumber = cmd(R,R,R,R,R,R,R,R,R,R,R), -- 11R
digitalnumberz = cmd(R,R,R,R,R,R,R,R,R,R,R,R), -- 12R
minitext = cmd(R,R,R,R,R),
ldist = cmd(W,R,R),
lineintersect = cmd(R,R,R,R,R,R,R,R,R,R,W,W,W,W), -- 10R 4W
rayintersect = cmd(R,R,R,R,R,R,R,R,R,R,W,W,W,W), -- 10R 4W
loadmapstate = cmd(),
savemapstate = cmd(),
movesprite = cmd(R,R,R,R,R,W),
neartag = cmd(R,R,R,R,R,W,W,W,W,R,R),
operateactivators = cmd(R,R),
operatesectors = cmd(R,R),
palfrom = (sp1 * t_define)^-4
/ handle_palfrom,
operate = cmd() * #sp1
/ "_con._operate(_aci)",
myos = cmd(R,R,R,R,R),
myosx = cmd(R,R,R,R,R),
myospal = cmd(R,R,R,R,R,R),
myospalx = cmd(R,R,R,R,R,R),
headspritesect = cmd(R,R),
headspritestat = cmd(R,R),
nextspritesect = cmd(R,R),
nextspritestat = cmd(R,R),
prevspritesect = cmd(R,R),
prevspritestat = cmd(R,R),
readarrayfromfile = cmd(I,D),
writearraytofile = cmd(I,D),
redefinequote = sp1 * t_define * newline_term_string,
resizearray = cmd(I,R),
getarraysize = cmd(I,W),
rotatepoint = cmd(R,R,R,R,R,W,W),
rotatesprite = cmd(R,R,R,R,R,R,R,R,R,R,R,R), -- 12R
rotatesprite16 = cmd(R,R,R,R,R,R,R,R,R,R,R,R), -- 12R
sectorofwall = cmd(W,R,R),
sectclearinterpolation = cmd(R),
sectsetinterpolation = cmd(R),
sectgethitag = cmd(),
sectgetlotag = cmd(),
spgethitag = cmd(),
spgetlotag = cmd(),
showview = cmd(R,R,R,R,R,R,R,R,R,R), -- 10R
showviewunbiased = cmd(R,R,R,R,R,R,R,R,R,R), -- 10R
smaxammo = cmd(R,R),
gmaxammo = cmd(R,W),
spriteflags = cmd(R), -- also see outer
ssp = cmd(R,R),
startlevel = cmd(R,R),
starttrack = cmd(D),
stopactorsound = cmd(R,R),
stopallsounds = cmd(),
updatesector = cmd(R,R,W),
updatesectorz = cmd(R,R,R,W),
getactorangle = cmd(W),
setactorangle = cmd(R),
getplayerangle = cmd(W),
setplayerangle = cmd(R),
getangletotarget = cmd(W),
getceilzofslope = cmd(R,R,R,W),
getflorzofslope = cmd(R,R,R,W),
getcurraddress = cmd(W), -- XXX
getkeyname = cmd(R,R,R),
getpname = cmd(R,R),
gettextureceiling = cmd(),
gettexturefloor = cmd(),
getticks = cmd(W),
gettimedate = cmd(W,W,W,W,W,W,W,W),
getzrange = cmd(R,R,R,R,W,W,W,W,R,R),
setactorsoundpitch = cmd(R,R,R),
setaspect = cmd(R,R),
}
local Cif = {
ifai = cmd(AI)
/ ACS":has_ai(%1)",
ifaction = cmd(AC)
/ ACS":has_action(%1)",
ifmove = cmd(MV)
/ ACS":has_move(%1)",
ifrnd = cmd(D)
/ "_con.rnd(%1)",
ifpdistl = cmd(D)
/ "_dist<%1", -- TODO: maybe set actor[].timetosleep afterwards
ifpdistg = cmd(D)
/ "_dist>%1", -- TODO: maybe set actor[].timetosleep afterwards
ifactioncount = cmd(D)
/ ACS":get_acount()==%1",
ifcount = cmd(D)
/ ACS":get_count()==%1",
ifactor = cmd(D)
/ SPS".picnum==%d",
ifstrength = cmd(D)
/ SPS".extra<=%d",
ifspawnedby = cmd(D)
/ ACS".picnum==%d",
ifwasweapon = cmd(D)
/ ACS".picnum==%d",
ifgapzl = cmd(D) -- factor into a con.* function?
/ format("_bit.arshift(%s-%s,8)<%%1", ACS".floorz", ACS".ceilingz"),
iffloordistl = cmd(D)
/ format("(%s-%s)<=256*%%1", ACS".floorz", SPS".z"),
ifceilingdistl = cmd(D)
/ format("(%s-%s)<=256*%%1", SPS".z", ACS".ceilingz"),
ifphealthl = cmd(D)
/ format("sprite[%s].extra<%%1", PLS".i"),
ifspritepal = cmd(D)
/ SPS".pal==%1",
ifgotweaponce = cmd(D)
/ "false", -- TODO? (multiplayer only)
ifangdiffl = cmd(D)
/ format("_con._angdiffabs(%s,%s)<=%%1", PLS".ang", SPS".ang"),
ifsound = cmd(D)
/ "",
-- vvv TODO: this is not correct for GET_ACCESS or GET_SHIELD.
-- Additionally, it accesses the current sprite unconditinally
-- (will throw error if invalid).
ifpinventory = cmd(D,D)
/ format("_con._getinventory(%s,%%1,%s)~=%%2", PLS"", SPS".pal"),
ifvarl = cmd(R,D),
ifvarg = cmd(R,D),
ifvare = cmd(R,D),
ifvarn = cmd(R,D),
ifvarand = cmd(R,D),
ifvaror = cmd(R,D),
ifvarxor = cmd(R,D),
ifvareither = cmd(R,D),
ifvarvarg = cmd(R,R),
ifvarvarl = cmd(R,R),
ifvarvare = cmd(R,R),
ifvarvarn = cmd(R,R),
ifvarvarand = cmd(R,R),
ifvarvaror = cmd(R,R),
ifvarvarxor = cmd(R,R),
ifvarvareither = cmd(R,R),
ifactorsound = cmd(R,R),
ifp = (sp1 * t_define)^1
/ "false", -- TODO
ifsquished = cmd()
/ "false", -- TODO
ifserver = cmd(),
ifrespawn = cmd()
/ "false", -- TODO
ifoutside = cmd()
/ format("_bit.band(sector[%s].ceilingstat,1)~=0", SPS".sectnum"),
ifonwater = cmd()
/ format("sectnum[%s].lotag==1 and _math.abs(%s-sector[%s].floorz)<32*256",
SPS".sectnum", SPS".z", SPS".sectnum"),
ifnotmoving = cmd()
/ "_bit.band(actor[_aci].movflag,49152)>16384",
ifnosounds = cmd(),
ifmultiplayer = cmd()
/ "false", -- TODO?
ifinwater = cmd()
/ format("sector[%s].lotag==2", SPS".sectnum"),
ifinspace = cmd()
/ "false", -- TODO
ifinouterspace = cmd()
/ "false", -- TODO
ifhitweapon = cmd()
/ "_con._A_IncurDamage(_aci)",
ifhitspace = cmd()
/ "_con._testkey(_pli,29)", -- XXX
ifdead = cmd()
/ SPS".extra<=0",
ifclient = cmd(),
ifcanshoottarget = cmd()
/ "false", -- TODO
ifcanseetarget = cmd() -- TODO: maybe set timetosleep afterwards
/ format("_con._canseetarget(%s,%s)", SPS"", PLS""),
ifcansee = cmd() * #sp1,
ifbulletnear = cmd()
/ "_con._bulletnear(_aci)",
ifawayfromwall = cmd()
/ format("_con._awayfromwall(%s,108)", SPS""),
ifactornotstayput = cmd()
/ ACS".actorstayput==-1",
}
----==== Tracing and reporting ====----
local string = require("string")
-- g_newlineidxs will contain the 1-based file offsets to "\n" characters
local g_newlineidxs = {}
-- Returns index into the sorted table tab such that
-- tab[index] <= searchelt < tab[index+1].
-- Preconditions:
-- tab[i] < tab[i+1] for 0 <= i < #tab
-- tab[0] <= searchelt < tab[#tab]
-- If #tab is less than 2, returns 0. This plays nicely with newline index
-- tables like { [0]=0, [1]=len+1 }, e.g. if the file doesn't contain any.
local function bsearch(tab, searchelt)
-- printf("bsearch(tab, %d)", searchelt)
local l, r = 0, #tab
local i
if (r < 2) then
return 0
end
while (l ~= r) do
i = l + math.ceil((r-l)/2) -- l < i <= r
assert(l < i and i <= r)
local elt = tab[i]
-- printf("l=%d tab[%d]=%d r=%d", l, i, elt, r)
if (searchelt == elt) then
return i
end
if (searchelt < elt) then
r = i-1
else -- (searchelt > elt)
l = i
end
end
-- printf("return tab[%d]=%d", l, tab[l])
return l
end
function getlinecol(pos) -- local
assert(type(pos)=="number")
local line = bsearch(g_newlineidxs, pos)
assert(line and g_newlineidxs[line]<=pos and pos<g_newlineidxs[line+1])
local col = pos-g_newlineidxs[line]
return line+1, col-1
end
-- A generic trace function, prints a position together with the match content.
-- The 'doit' parameter can be used to temporarily enable/disable a particular
-- tracing function.
local function TraceFunc(pat, label, doit)
assert(doit ~= nil)
pat = Pat(pat)
if (doit) then
local function tfunc(subj, pos, a)
printf("%s:%s: %s", linecolstr(pos), label, a)
return true
end
pat = lpeg.Cmt(pat, tfunc)
elseif (label=="kw") then -- HACK
local function tfunc(subj, pos, a)
g_lastkwpos = pos
g_lastkw = a
return true
end
-- XXX: is there a better way?
pat = lpeg.Cmt(pat, tfunc)
end
return pat
end
local function BadIdent(pat)
local function tfunc(subj, pos, a)
if (g_warn["bad-identifier"] and not g_badids[a]) then
warnprintf("bad identifier: %s", a)
g_badids[a] = true
end
return true
end
return lpeg.Cmt(Pat(pat), tfunc)
end
-- These are tracers for specific patterns which can be disabled
-- if desired.
local function Keyw(kwname) return TraceFunc(kwname, "kw", false) end
local function NotKeyw(text) return TraceFunc(text, "!kw", false) end
local function Ident(idname) return TraceFunc(idname, "id", false) end
local function Stmt(cmdpat) return TraceFunc(cmdpat, "st", false) end
--local function Temp(kwname) return TraceFunc(kwname, "temp", true) end
--Ci["myosx"] = Temp(Ci["myosx"])
----==== Translator continued ====----
local function after_inner_cmd_Cmt(subj, pos, ...)
local capts = {...}
if (g_numerrors == inf) then
return nil
end
if (type(capts[1])=="string" and capts[2]==nil) then
return true, capts[1] .."--"..linecolstr(pos) --TEMP
end
return true
end
local function after_if_cmd_Cmt(subj, pos, ...)
local capts = {...}
if (g_numerrors == inf) then
return nil
end
if (type(capts[1])=="string" and capts[2]==nil) then
return true, capts[1]
end
return true
end
local function after_cmd_Cmt(subj, pos, ...)
if (g_numerrors == inf) then
-- print("Aborting parsing...")
return nil -- make the match fail, bail out of parsing
end
return true -- don't return any captures
end
-- attach the command names at the front!
local function attachnames(kwtab, matchtimefunc)
for cmdname,cmdpat in pairs(kwtab) do
-- The match-time function capture at the end is so that every
-- command acts as a barrier to captures to prevent stack overflow (and
-- to make lpeg.match return a subject position at the end)
kwtab[cmdname] = lpeg.Cmt(Keyw(cmdname) * cmdpat, matchtimefunc)
end
end
attachnames(Co, after_cmd_Cmt)
attachnames(Ci, after_inner_cmd_Cmt)
attachnames(Cif, after_if_cmd_Cmt)
-- Takes one or more tables and +'s all its patterns together in reverse
-- lexicographical order.
-- Each such PATTAB must be a table that maps command names to their patterns.
local function all_alt_pattern(...)
local cmds = {}
local args = {...}
assert(#args <= 2)
for argi=1,#args do
local pattab = args[argi]
-- pairs() iterates in undefined order, so we first fill in the names...
for cmdname,_ in pairs(pattab) do
cmds[#cmds+1] = cmdname
end
end
-- ...and then sort them in ascending lexicographical order
table.sort(cmds)
local pat = Pat(false)
for i=1,#cmds do
local ourpat = args[1][cmds[i]] or args[2][cmds[i]]
-- shorter commands go at the end!
pat = pat + ourpat
end
return pat
end
-- actor ORGANTIC is greeting!
local function warn_on_lonely_else(pos)
pwarnprintf(pos, "found `else' with no `if'")
end
local con_inner_command = all_alt_pattern(Ci)
local con_if_begs = all_alt_pattern(Cif)
local lone_else = (POS() * "else" * sp1)/warn_on_lonely_else
local stmt_list = Var("stmt_list")
-- possibly empty statement list:
local stmt_list_or_eps = lpeg.Ct((stmt_list * sp1)^-1)
local stmt_list_nosp_or_eps = (stmt_list * (sp1 * stmt_list)^0)^-1
-- common to actor and useractor: <name/tilenum> [<strength> [<action> [<move> [<flags>... ]]]]
local common_actor_end = sp1 * lpeg.Ct(t_define *
(sp1 * t_define *
(sp1 * t_action *
(sp1 * t_move *
(sp1 * t_define)^0
)^-1
)^-1
)^-1)
* sp1 * stmt_list_or_eps * "enda"
--== block delimiters (no recursion) ==--
local Cb = {
-- actor (...)
actor = lpeg.Cc(nil) * common_actor_end / on_actor_end,
-- useractor <actortype> (...)
useractor = sp1 * t_define * common_actor_end / on_actor_end,
-- eventloadactor <name/tilenum>
eventloadactor = lpeg.Cc(nil) * sp1 * lpeg.Ct(t_define)
* sp1 * stmt_list_or_eps * "enda" / on_actor_end,
onevent = sp1 * t_define * sp1 * stmt_list_or_eps * "endevent",
state = sp1 * t_identifier * sp1 * stmt_list_or_eps * "ends"
/ on_state_end,
}
attachnames(Cb, after_cmd_Cmt)
local t_good_identifier = Range("AZ", "az", "__") * Range("AZ", "az", "__", "09")^0
-- CON isaltok also has chars in "{}.", but these could potentially
-- interfere with *CON* syntax. The "]" is so that the number in e.g. array[80]
-- isn't considered a broken identifier.
-- "-" is somewhat problematic, but we allow it only as 2nd and up character, so
-- there's no ambiguity with unary minus. (Commands must be separated by spaces
-- in CON, so a trailing "-" is "OK", too.)
-- This is broken in itself, so we ought to make a compatibility/modern CON switch.
local t_broken_identifier = BadIdent(-((t_number + t_good_identifier) * (sp1 + Set("[]:"))) *
(alphanum + Set("_/\\*?")) * (alphanum + Set("_/\\*-+?"))^0)
local function begin_if_fn(condstr)
g_ifseqlevel = g_ifseqlevel+1
condstr = condstr or "TODO"
assert(type(condstr)=="string")
return format("if (%s) then", condstr)
end
local function end_if_fn()
g_ifseqlevel = g_ifseqlevel-1
end
local function check_else_Cmt()
-- match an 'else' only at the outermost level
local good = (g_ifseqlevel==0)
if (good) then
return good, "else"
end
-- return nothing, making the Cmt fail
end
--- The final grammar!
local Grammar = Pat{
-- The starting symbol.
-- A translation unit is a (possibly empty) sequence of outer CON
-- commands, separated by at least one whitespace which may be
-- omitted at the EOF.
sp0 * (all_alt_pattern(Co, Cb) * sp1)^0,
-- Some often-used terminals follow. These appear here because we're
-- hitting a limit with LPeg else.
-- http://lua-users.org/lists/lua-l/2008-11/msg00462.html
-- NOTE: NW demo (NWSNOW.CON) contains a Ctrl-Z char (decimal 26)
whitespace = Set(" \t\r\26") + newline + Set("(),;") + comment + linecomment,
t_identifier_all = t_broken_identifier + t_good_identifier,
-- NOTE: -conl.keyword alone would be wrong, e.g. "state breakobject":
-- NOTE 2: The + "[" is so that stuff like
-- getactor[THISACTOR].x x
-- getactor[THISACTOR].y y
-- is parsed correctly. (Compared with this:)
-- getactor[THISACTOR].x x
-- getactor [THISACTOR].y y
-- This is in need of cleanup!
t_identifier = -NotKeyw(conl.keyword * (sp1 + "[")) * lpeg.C(t_identifier_all),
t_define = (POS() * lpeg.C(t_maybe_minus) * t_identifier / lookup_defined_label) + t_number,
t_move =
POS()*t_identifier / function(...) return lookup_composite(LABEL.MOVE, ...) end +
POS()*t_number / function(...) return check_composite_literal(LABEL.MOVE, ...) end,
t_ai =
POS()*t_identifier / function(...) return lookup_composite(LABEL.AI, ...) end +
POS()*t_number / function(...) return check_composite_literal(LABEL.AI, ...) end,
t_action =
POS()*t_identifier / function(...) return lookup_composite(LABEL.ACTION, ...) end +
POS()*t_number / function(...) return check_composite_literal(LABEL.ACTION, ...) end,
t_arrayexp = t_identifier * arraypat * memberpat^-1,
-- SWITCH
switch_stmt = Keyw("switch") * sp1 * t_rvar *
(Var("case_block") + Var("default_block"))^0 * sp1 * "endswitch",
-- NOTE: some old DNWMD has "case: PIGCOP". I don't think I'll allow that.
case_block = (sp1 * Keyw("case") * sp1 * t_define/"XXX_CASE" * (sp0*":")^-1)^1 * sp1 *
stmt_list_nosp_or_eps, -- * "break",
default_block = sp1 * Keyw("default") * (sp0*":"*sp0 + sp1) * stmt_list_nosp_or_eps, -- * "break",
if_stmt = con_if_begs/begin_if_fn * sp1
* Var("single_stmt") * (Pat("")/end_if_fn)
* (sp1 * lpeg.Cmt(Pat("else"), check_else_Cmt) * sp1 * Var("single_stmt"))^-1
* lpeg.Cc("end"),
-- TODO?: SST TC has "state ... else ends"
while_stmt = Keyw("whilevarvarn") * sp1 * t_rvar * sp1 * t_rvar * sp1 * Var("single_stmt")
+ Keyw("whilevarn") * sp1 * t_rvar * sp1 * t_define/"WHILE_XXX" * sp1 * Var("single_stmt"),
-- TODO: some sp1 --> sp0?
single_stmt = Stmt(
lone_else^-1 *
( Keyw("{") * sp1 * "}" -- space separation of commands in CON is for a reason!
+ Keyw("{") * sp1 * stmt_list * sp1 * "}"
+ (con_inner_command + Var("switch_stmt") + Var("if_stmt") + Var("while_stmt"))
-- + lpeg.Cmt(t_newline_term_str, function (subj, curpos) print("Error at "..curpos) end)
)),
-- a non-empty statement/command list
stmt_list = Var("single_stmt") * (sp1 * Var("single_stmt"))^0,
}
local math = require("math")
local function setup_newlineidxs(contents)
local newlineidxs = {}
for i in string.gmatch(contents, "()\n") do
newlineidxs[#newlineidxs+1] = i
end
if (#newlineidxs == 0) then
-- try CR only (old Mac)
for i in string.gmatch(contents, "()\r") do
newlineidxs[#newlineidxs+1] = i
end
-- if (#newlineidxs > 0) then print('CR-only lineends detected.') end
end
-- dummy newlines at beginning and end
newlineidxs[#newlineidxs+1] = #contents+1
newlineidxs[0] = 0
return newlineidxs
end
---
local function do_flatten_codetab(code, intotab)
for i=1,math.huge do
local elt = code[i]
if (type(elt)=="string") then
intotab[#intotab+1] = elt
elseif (type(elt)=="table") then
do_flatten_codetab(elt, intotab)
else
assert(elt==nil)
return
end
end
end
-- Return a "string buffer" table that can be table.concat'ed
-- to get the code string.
local function flatten_codetab(codetab)
local tmpcode = {}
do_flatten_codetab(codetab, tmpcode)
return tmpcode
end
---=== EXPORTED FUNCTIONS ===---
local function new_initial_perfile_codetab()
return { "local _con=require'con'; local _bit=require'bit'" }
end
function parse(contents) -- local
-- save outer state
local lastkw, lastkwpos, numerrors = g_lastkw, g_lastkwpos, g_numerrors
local newlineidxs = g_newlineidxs
local curcode = g_curcode
g_ifseqlevel = 0
g_curcode = new_initial_perfile_codetab()
g_file_code[g_filename] = g_curcode
-- set up new state
-- TODO: pack into one "parser state" table?
g_lastkw, g_lastkwpos, g_numerrors = nil, nil, 0
g_newlineidxs = setup_newlineidxs(contents)
g_recurslevel = g_recurslevel+1
local idx = lpeg.match(Grammar, contents)
if (not idx) then
printf("[%d] Match failed.", g_recurslevel)
g_numerrors = inf
elseif (idx == #contents+1) then
if (g_numerrors ~= 0) then
printf("[%d] Matched whole contents (%d errors).",
g_recurslevel, g_numerrors)
elseif (g_recurslevel==0) then
print("[0] Matched whole contents.")
end
else
local i, col = getlinecol(idx)
local bi, ei = g_newlineidxs[i-1]+1, g_newlineidxs[i]-1
printf("[%d] Match succeeded up to %d (line %d, col %d; len=%d)",
g_recurslevel, idx, i, col, #contents)
g_numerrors = inf
-- printf("Line goes from %d to %d", bi, ei)
local suffix = ""
if (ei-bi > 76) then
ei = bi+76
suffix = " (...)"
end
print(string.sub(contents, bi, ei)..suffix)
if (g_lastkwpos) then
i, col = getlinecol(g_lastkwpos)
printf("Last keyword was at line %d, col %d: %s", i, col, g_lastkw)
end
end
g_curcode = curcode
g_recurslevel = g_recurslevel-1
-- restore outer state
g_lastkw, g_lastkwpos = lastkw, lastkwpos
g_numerrors = (g_numerrors==inf and inf) or numerrors
g_newlineidxs = newlineidxs
end
local function handle_cmdline_arg(str)
if (str:sub(1,1)=="-") then
if (#str == 1) then
printf("Warning: input from stdin not supported")
else
local ok = false
local kind = str:sub(2,2)
if (kind=="W" and #str >= 3) then
-- warnings
local val = true
local warnstr = str:sub(3)
if (#warnstr >= 4 and warnstr:sub(1,3)=="no-") then
val = false
warnstr = warnstr:sub(4)
end
if (type(g_warn[warnstr])=="boolean") then
g_warn[warnstr] = val
ok = true
end
end
if (not ok) then
printf("Warning: Unrecognized option %s", str)
end
end
return true
end
end
if (not _EDUKE32_LUNATIC) then
--- stand-alone
local i = 1
while (arg[i]) do
if (handle_cmdline_arg(arg[i])) then
table.remove(arg, i)
else
i = i+1
end
end
for argi=1,#arg do
local filename = arg[argi]
g_recurslevel = -1
g_badids = {}
reset_labels()
reset_gamedata()
reset_codegen()
g_numerrors = 0
g_directory = filename:match("(.*/)") or ""
filename = filename:sub(#g_directory+1, -1)
-- NOTE: xpcall isn't useful here since the traceback won't give us
-- anything inner to the lpeg.match call
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 (g_lastkwpos ~= nil) then
printf("LAST KEYWORD POSITION: %s, %s", linecolstr(g_lastkwpos), g_lastkw)
end
print(msg)
end
--[[
local file = io.stdout
for filename,codetab in pairs(g_file_code) do
file:write(format("-- GENERATED CODE for \"%s\":\n", filename))
file:write(table.concat(flatten_codetab(codetab), "\n"))
file:write("\n")
end
--]]
end
else
--- embedded
return { parse=parse }
end