1-- LunaCON CON to Lunatic translator
2-- requires LPeg, http://www.inf.puc-rio.br/~roberto/lpeg/lpeg.html
3
4local require = require
5local lpeg = require("lpeg")
6
7local bit
8local math = require("math")
9local string = require("string")
10local table = require("table")
11
12
13local arg = arg
14
15local assert = assert
16local error = error
17local ipairs = ipairs
18local loadstring = loadstring
19local pairs = pairs
20local pcall = pcall
21local print = print
22local setmetatable = setmetatable
23local tonumber = tonumber
24local tostring = tostring
25local type = type
26local unpack = unpack
27
28-- non-nil if running from EDuke32
29-- (read_into_string~=nil  iff  string.dump==nil)
30local read_into_string = read_into_string
31local ffi, ffiC
32
33if (string.dump) then  -- running stand-alone
34    local ljp = pcall(function() require("ffi") end)
35    -- "lbit" is the same module as LuaJIT's "bit" (LuaBitOp:
36    -- http://bitop.luajit.org/), but under a different name for (IMO) less
37    -- confusion. Useful for running with Rio Lua for cross-checking.
38    bit = ljp and require("bit") or require("lbit")
39    require("strict")
40else
41    bit = require("bit")
42    ffi = require("ffi")
43    ffiC = ffi.C
44end
45
46
47
48module("lunacon")
49
50
51-- I think that the "too many pending calls/choices" is unavoidable in general.
52-- This limit is of course still arbitrary, but writing long if/else cascades
53-- in CON isn't pretty either (though sometimes necessary because nested switches
54-- don't work?)
55-- See also:  http://lua-users.org/lists/lua-l/2010-03/msg00086.html
56lpeg.setmaxstack(1024);
57
58
59local Pat, Set, Range, Var = lpeg.P, lpeg.S, lpeg.R, lpeg.V
60local POS, Cc, Ctab = lpeg.Cp, lpeg.Cc, lpeg.Ct
61
62-- CON language definitions (among other things, all keywords pattern).
63local conl = require("con_lang")
64
65
66local function match_until(matchsp, untilsp)  -- (!untilsp matchsp)* in PEG
67    -- sp: string or pattern
68    return (matchsp - Pat(untilsp))^0
69end
70
71local format = string.format
72--[[
73format = function(fmt, ...)
74    local ok, res = pcall(string.format, fmt, ...)
75    if (not ok) then
76        error(string.format("FAILED format(%q, ...) | message: %s", fmt, res))
77    end
78    return res
79end
80--]]
81
82local function printf(fmt, ...)
83    print(format(fmt, ...))
84end
85
86--- some constants
87
88local C = {
89    -- These two are not used except for predefined labels.
90    -- NOTE: in-game, MAXSPRITES may be 4096 for a V7 build!
91    MAXSTATUS = ffiC and ffiC.MAXSTATUS or 1024,
92    MAXSPRITES = ffiC and ffiC.MAXSPRITES or 16384,
93
94    MAXTILES = ffiC and ffiC.MAXTILES or 30720,
95    MAX_WEAPONS = ffiC and ffiC.MAX_WEAPONS or 12,
96}
97
98---=== semantic action functions ===---
99
100local inf = 1/0
101local NaN = 0/0
102
103-- Last keyword position, for error diagnosis.
104local g_lastkwpos = nil
105local g_lastkw = nil
106local g_badids = {}  -- maps bad id strings to 'true'
107
108local g_recurslevel = -1  -- 0: base CON file, >0 included
109local g_filename = "???"
110local g_directory = ""  -- with trailing slash if not empty
111local g_maxerrors = 20
112local g_numerrors = 0
113
114-- Default directory to search for GAME.CON etc.
115-- Stand-alone LunaCON only.
116local g_defaultDir = nil
117
118-- Warning options. Key names are the same as cmdline options, e.g.
119-- -Wno-bad-identifier for disabling the "bad identifier" warning.
120local g_warn = { ["not-redefined"]=true, ["bad-identifier"]=false,
121                 ["number-conversion"]=true, ["system-gamevar"]=true,
122                 ["error-bad-getactorvar"]=false, ["chained-loadactor"]=true,
123                 ["never-used-gamevar"]=false, ["never-read-gamevar"]=false, }
124
125-- Code generation and output options.
126local g_cgopt = { ["no"]=false, ["debug-lineinfo"]=false, ["gendir"]=nil,
127                  ["cache-sap"]=false, ["error-nostate"]=true,
128                  ["playervar"]=true, ["trapv"]=false, ["wrapv"]=false,
129                  ["bad-getactorvar-use-pli"]=true,
130                  ["error-nonlocal-userdef"]=true,
131                  ["error-negative-tag-write"]=false, }
132
133if (string.dump) then
134    g_cgopt["names"] = false
135end
136
137-- For -fnames mode.
138local g_actorTileToName = {}
139
140local function csapp() return g_cgopt["cache-sap"] end
141
142local function handle_cmdline_arg(str)
143    if (str:sub(1,1)=="-") then
144        if (#str == 1) then
145            printf("Warning: input from stdin not supported")
146        else
147            local ok = false
148            local kind = str:sub(2,2)
149
150            -- -W(no-)*: warnings
151            if (kind=="W" and #str >= 3) then
152                local val = true
153                local warnstr = str:sub(3)
154
155                if (warnstr == "all") then
156                    -- Enable all warnings.
157                    for wopt in pairs(g_warn) do
158                        g_warn[wopt] = true
159                    end
160                    ok = true
161                else
162                    -- Enable or disable a particular warning.
163                    if (warnstr:sub(1,3)=="no-") then
164                        val = false
165                        warnstr = warnstr:sub(4)
166                    end
167
168                    if (type(g_warn[warnstr])=="boolean") then
169                        g_warn[warnstr] = val
170                        ok = true
171                    end
172                end
173
174            -- -fno* special handling
175            elseif (str:sub(2)=="fno") then
176                -- Disable printing code entirely.
177                g_cgopt["no"] = true
178                ok = true
179            elseif (str:sub(2)=="fno=onlycheck") then
180                -- Disable printing code, only do syntax check of gen'd code.
181                g_cgopt["no"] = "onlycheck"
182                ok = true
183
184            -- -fgendir=<directory>: specify directory for generated code
185            elseif (str:sub(2,9)=="fgendir=" and #str >= 10) then
186                g_cgopt["gendir"] = str:sub(10)
187                ok = true
188
189            -- -f(no-)*: code generation options
190            elseif (kind=="f" and #str >= 3) then
191                local val = true
192                local cgstr = str:sub(3)
193
194                if (cgstr:sub(1,3)=="no-") then
195                    val = false
196                    cgstr = cgstr:sub(4)
197                end
198
199                if (type(g_cgopt[cgstr])=="boolean") then
200                    g_cgopt[cgstr] = val
201                    ok = true
202                end
203
204            -- -I<directory>: default search directory (only ONCE, not search path)
205            elseif (kind=="I" and #str >= 3) then
206                g_defaultDir = str:sub(3)
207                ok = true
208            end
209
210            if (not ffi and not ok) then
211                printf("Warning: Unrecognized option %s", str)
212            end
213        end
214
215        return true
216    end
217end
218
219-- Handle command line arguments. Has to happen before pattern construction,
220-- because some of them depend on codegen options (specifically, -ftrapv,
221-- -fwrapv).
222if (string.dump) then
223    -- running stand-alone
224    local i = 1
225    while (arg[i]) do
226        if (handle_cmdline_arg(arg[i])) then
227            table.remove(arg, i)  -- remove processed cmdline arg
228        else
229            i = i+1
230        end
231    end
232else
233    -- running from EDuke32
234    local i=0
235    while (ffiC.g_argv[i] ~= nil) do
236        handle_cmdline_arg(ffi.string(ffiC.g_argv[i]))
237        i = i+1
238    end
239end
240
241if (g_cgopt["error-negative-tag-write"]) then
242    conl.setup_negative_tag_check("_st")
243end
244
245-- Stack with *true* on top if the innermost block is a "whilevar*n".
246local g_isWhile = {}
247-- Sequence number of 'while' statements, used to implement CON "break" inside
248-- whilevar*n, which really behaves like what sane languages call "continue"...
249local g_whilenum = 0
250
251---=== Code generation ===---
252local GVFLAG = {
253    PERPLAYER=1, PERACTOR=2, PERX_MASK=3,
254    SYSTEM   = 0x00000800,
255    READONLY = 0x00001000,
256
257    NODEFAULT = 0x00000400,  -- don't reset on actor spawn
258    NORESET   = 0x00020000,  -- don't reset when restoring map state
259
260    CON_PERPLAYER = 0x40000000,  -- LunaCON internal
261}
262
263-- NOTE: This differs from enum GamevarFlags_t's GAMEVAR_USER_MASK
264GVFLAG.USER_MASK = GVFLAG.PERX_MASK + GVFLAG.NODEFAULT + GVFLAG.NORESET
265
266-- CON --> mangled Lua function name, also existence check:
267local g_funcname = {}
268-- while parsing a block, it is a table of "gencode" tables:
269local g_switchCode = nil
270-- Global number of switch statements:
271local g_switchCount = 0
272-- Number of session gamevars:
273local g_numSessionVars = 0
274-- [identifier] = { name=<mangled name / code>, flags=<gamevar flags> }
275local g_gamevar = {}
276-- [identifier] = { name=<mangled name / code>, size=<initial size> }
277local g_gamearray = {}
278
279-- * nil if dynamic tile remapping disabled
280-- * {} if enabled but no remappings made
281-- * else, a nonempty table { [name]=<g_dynTileList index> }
282local g_dyntilei = nil
283-- Analogously for sounds.
284local g_dynsoundi = nil
285
286local g_have_file = {}  -- [filename]=true
287local g_curcode = nil  -- a table of string pieces or other "gencode" tables
288
289-- will be a table, see reset.codegen()
290local g_code = nil
291
292
293local function ACS(s) return (csapp() and "_a" or "actor[_aci]")..s end
294local function SPS(s) return (csapp() and "_spr" or "sprite[_aci]")..s end
295local function PLS(s) return (csapp() and "_ps" or "player[_pli]")..s end
296local function PLSX(s) return "player[_pli]"..s end
297
298
299local function getlinecol(pos) end -- fwd-decl
300
301local function new_initial_codetab()
302    -- NOTE: Keep this one line per line to not confuse the Lua->CON line
303    -- mapping system.
304    return {
305        -- Requires.
306        "local require=require",
307        "local _con, _bit, _math = require'con', require'bit', require'math'",
308        "local _xmath = require'xmath'",
309
310        -- Cache globals into locals.
311        "local sector, sprite, wall, spriteext, _atsprite = sector, sprite, wall, spriteext, _atsprite",
312        "local actor, player, projectile, g_tile = actor, player, projectile, g_tile",
313        "local gameactor, gameevent, _gv = gameactor, gameevent, gv",
314        "local updatesector, updatesectorz, cansee = updatesector, updatesectorz, cansee",
315        "local print, printf = print, printf",
316
317        -- Cache a couple of often-used functions.
318        "local _div, _mod, _mulTR, _mulWR = _con._div, _con._mod, _con._mulTR, _con._mulWR",
319        "local _band, _bor, _bxor = _bit.band, _bit.bor, _bit.bxor",
320        "local _lsh, _rsh, _arsh = _bit.lshift, _bit.rshift, _bit.arshift",
321        "local _setsprite,_ssp = _con._setsprite,_con._ssp",
322        g_cgopt["error-nonlocal-userdef"]
323            and "local _gud=_con._get_userdef_check" or "local _gud=_con._get_userdef",
324        "local _st=_con._err_if_negative",
325
326        -- * CON "states" (subroutines) and
327        -- * Switch function table, indexed by global switch sequence number:
328        "local _F,_SW = {},{}",
329
330        -- CON gamevars and gamearrays (see mangle_name()), set up for
331        -- restoration from savegames.
332        "module(...)",
333        "_V,_A={},{}",
334        "-- NOTE to the reader: This require's result is Lunatic-private API! DO NOT USE!",
335        "local _dummy,_S=require'end_gamevars'",
336-- XXX: Currently commented out because of gamevar restoration from loadmapstate.
337--        "local _V,_A=_V,_A",
338        "local _C,_M,_I={},{},{}",  -- actions, moves, ais
339
340        -- Static ivec3s so that no allocations need to be made.
341        "local _IVEC = { _xmath.ivec3(), _xmath.ivec3() }",
342        "local function _IV(num, x, y, z)",
343        "  local v=_IVEC[num]; v.x=x; v.y=y; v.z=z; return v;",
344        "end",
345           }
346end
347
348-- CON global system gamevar
349local function CSV(var) return "_gv._csv"..var end
350
351-- Creates the table of predefined game variables.
352-- KEEPINSYNC gamevars.c: Gv_AddSystemVars()
353local function new_initial_gvartab()
354    local wmembers = conl.wdata_members
355
356    local function GamevarCreationFunc(addflags)
357        return function(varname)
358            -- 'used' is a bitmask: 1 is 'was read', 2 is 'was written to'
359            return { name=varname, flags=GVFLAG.SYSTEM+addflags, used=3 }
360        end
361    end
362
363    local RW = GamevarCreationFunc(0)
364    local RO = GamevarCreationFunc(GVFLAG.READONLY)
365    local PRW = GamevarCreationFunc(GVFLAG.PERPLAYER)
366    local PRO = GamevarCreationFunc(GVFLAG.READONLY+GVFLAG.PERPLAYER)
367
368    local gamevar = {
369        -- NOTE: THISACTOR can mean different things in some contexts.
370        THISACTOR = RO "_aci",
371
372        RETURN = RW "_gv.RETURN",
373        HITAG = RW(CSV".HITAG"),
374        LOTAG = RW(CSV".LOTAG"),
375        TEXTURE = RW(CSV".TEXTURE"),
376
377        -- This will warn when defining from CON, but it's the most
378        -- straightforward implementation.
379        LOGO_FLAGS = RW "_gv.g_logoFlags",
380
381        xdim = RO "_gv.xdim",
382        ydim = RO "_gv.ydim",
383        windowx1 = RO "_gv.windowxy1.x",
384        windowy1 = RO "_gv.windowxy1.y",
385        windowx2 = RO "_gv.windowxy2.x",
386        windowy2 = RO "_gv.windowxy2.y",
387
388        yxaspect = RO "_gv._get_yxaspect()",
389        viewingrange = RO "_gv._get_viewingrange()",
390        -- TODO: gravitationalconstant, gametype_flags
391
392        numsectors = RO "_gv.numsectors",
393        NUMSECTORS = RO "_gv.numsectors",
394        NUMWALLS = RO "_gv.numwalls",
395        Numsprites = RO "_gv.Numsprites",
396
397        randomseed = RW "_gv.randomseed",
398        totalclock = RO "_gv.totalclock",
399        framerate = RO "_gv._currentFramerate()",
400        current_menu = RO "_gv._currentMenu()",
401        rendmode = RO "_gv.rendmode",
402
403        screenpeek = RO "_gv.screenpeek",
404
405        camerax = RW "_gv.cam.pos.x",
406        cameray = RW "_gv.cam.pos.y",
407        cameraz = RW "_gv.cam.pos.z",
408        cameraang = RW "_gv.cam.ang",
409        camerahoriz = RW "_gv.cam.horiz",
410        camerasect = RW "_gv.cam.sect",
411        cameradist = RW "_gv.cam.dist",
412        cameraclock = RW "_gv.cam.clock",
413
414        -- HUD weapon gamevars
415        currentweapon = RW "_gv.hudweap.cur",
416        weaponcount = RW "_gv.hudweap.count",
417        weapon_xoffset = RW "_gv.hudweap.gunposx",
418        looking_angSR1 = RW "_gv.hudweap.lookhalfang",
419        gun_pos = RW "_gv.hudweap.gunposy",
420        looking_arc = RW "_gv.hudweap.lookhoriz",
421        gs = RW "_gv.hudweap.shade",
422
423        -- Some per-player gamevars
424        ZRANGE = PRW(PLSX".zrange"),
425        ANGRANGE = PRW(PLSX".angrange"),
426        AUTOAIMANGLE = PRW(PLSX".autoaimang"),
427
428        PIPEBOMB_CONTROL = PRW(PLSX".pipebombControl"),
429        GRENADE_LIFETIME = PRW(PLSX".pipebombLifetime"),
430        GRENADE_LIFETIME_VAR = PRW(PLSX".pipebombLifetimeVar"),
431        TRIPBOMB_CONTROL = PRW(PLSX".tripbombControl"),
432        STICKYBOMB_LIFETIME = PRW(PLSX".tripbombLifetime"),
433        STICKYBOMB_LIFETIME_VAR = PRW(PLSX".tripbombLifetimeVar"),
434
435        -- Some *writable* system gamevars relating to multiplayer.
436        -- TODO_MP.
437        RESPAWN_MONSTERS = RO "0",
438        RESPAWN_ITEMS = RO "0",
439        RESPAWN_INVENTORY = RO "0",
440        MONSTERS_OFF = RO "0",
441        MARKER = RO "0",
442
443        -- These are not 100% authentic (they're only updated in certain
444        -- circumstances, see player.c: P_SetWeaponGamevars()). But IMO it's
445        -- more useful like this.
446        WEAPON = PRO(PLSX".curr_weapon"),
447        WORKSLIKE = PRO(format(PLSX".weapon[%s].workslike", PLSX".curr_weapon")),
448
449        VOLUME = RO "_gv._ud.volume_number",
450        LEVEL = RO "_gv._ud.level_number",
451    }
452
453    -- Reserved bits
454    gamevar.LOGO_FLAGS.rbits = bit.bnot(0x001fffff)
455
456    for w=0,C.MAX_WEAPONS-1 do
457        for i=1,#wmembers do
458            local member = wmembers[i]:gsub(".*_t ","")  -- strip e.g. "const int32_t "
459                                      :gsub("^_","")  -- strip potentially leading underscore
460            local name = format("WEAPON%d_%s", w, member:upper())
461            gamevar[name] = PRW(format(PLSX".weapon[%d].%s", w, member))
462
463            if (member=="flags") then
464                gamevar[name].rbits = bit.bnot(0x1ffff)
465            end
466        end
467    end
468
469    return gamevar
470end
471
472local reset = {}
473
474function reset.codegen()
475    g_funcname = {}
476    g_switchCode = nil
477    g_switchCount = 0
478    g_numSessionVars = 0
479    g_gamevar = new_initial_gvartab()
480    g_gamearray = {
481        -- SYSTEM_GAMEARRAY
482        tilesizx = { name="g_tile.sizx", size=C.MAXTILES, sysp=true },
483        tilesizy = { name="g_tile.sizy", size=C.MAXTILES, sysp=true },
484    }
485
486    g_dyntilei = nil
487    g_dynsoundi = nil
488
489    g_have_file = {}
490    g_curcode = new_initial_codetab()
491    -- actor, event, loadactor: [{actor, event, actor}num] = gencode_table
492    --
493    -- aflagsloc[actornum]: location of '(user)actor' token, 'spriteflags' or
494    -- 'sprite*' command; result of getLocation(<kind>, <pos>)
495    g_code = { actor={}, event={}, loadactor={}, aflagsloc={} }
496
497    g_recurslevel = -1
498    g_numerrors = 0
499end
500
501-- Is SYSTEM_GAMEARRAY?
502local function issysgar(str)
503    return str:match("^g_tile.siz[xy]")
504end
505
506local function addcode(x)
507    assert(type(x)=="string" or type(x)=="table")
508    g_curcode[#g_curcode+1] = x
509end
510
511local function addcodef(fmt, ...)
512    addcode(format(fmt, ...))
513end
514
515local function paddcodef(pos, fmt, ...)
516    addcodef(fmt.."--"..getlinecol(pos), ...)
517end
518
519local function add_code_and_end(codetab, endstr)
520    assert(type(codetab)=="table")
521    addcode(codetab)
522    addcode(endstr)
523end
524
525local function get_cache_sap_code()
526    return csapp() and "local _spr,_a,_ps=_con._getsap(_aci,_pli)" or ""
527end
528
529-- fwd-decls
530local warnprintf, errprintf, pwarnprintf, perrprintf, contprintf
531local getLocation
532
533local on = {}
534
535-- Map from CON actor usertype to SFLAGs.
536local MAP_ACTOR_FLAGS = {
537    [0] = 0,
538    [1] = conl.SFLAG.SFLAG_BADGUY,
539    [2] = conl.SFLAG.SFLAG_BADGUY + conl.SFLAG.SFLAG_BADGUYSTAYPUT,
540    [3] = conl.SFLAG.SFLAG_BADGUY + conl.SFLAG.SFLAG_BADGUYSTAYPUT,
541}
542for i=4,7 do
543    MAP_ACTOR_FLAGS[i] = MAP_ACTOR_FLAGS[i-4] + conl.SFLAG.SFLAG_ROTFIXED
544end
545
546
547-- Table of functions doing various lookups (label, gamevar, ...)
548local lookup = {}
549
550-- For -fnames mode.
551function on.fnames_tilenum_label(tilenum)
552    if (g_cgopt["names"] and type(tilenum)=="string") then
553        -- <tilenum> may be a string (define label)
554        -- HANDLE_RAWDEFINE
555        local pos, minus, label = tilenum:match("(.-):(.-):(.+)")
556        local realtilenum = lookup.defined_label(tonumber(pos), minus, label)
557
558        g_actorTileToName[realtilenum] = label
559        return true
560    end
561end
562
563function on.actor_end(pos, usertype, tsamm, codetab)
564    local tilenum = tsamm[1]
565    local flags = 0
566
567    if (on.fnames_tilenum_label(tilenum)) then
568        return
569    end
570
571    if (usertype ~= nil) then  -- useractor
572        if (not (bit.band(usertype, bit.bnot(7)) == 0)) then
573            perrprintf(pos, "invalid usertype: must be bitwise OR of 1, 2 and/or 4")
574        else
575            flags = MAP_ACTOR_FLAGS[usertype]
576        end
577    end
578
579    -- 0x08000000: actor.FLAGS.replace
580    flags = bit.bor(flags, 0x08000000)
581
582    local str = flags..","
583    for i=2,math.min(#tsamm,4) do
584        str = str .. tostring(tsamm[i])..","
585    end
586    if (#tsamm >= 5) then
587        local movflags = bit.bor(unpack(tsamm, 5))
588        str = str .. movflags..","
589    end
590
591    paddcodef(pos, "gameactor{%d,%sfunction(_aci,_pli,_dist)", tilenum, str)
592    addcode(get_cache_sap_code())
593    add_code_and_end(codetab, "end}")
594
595    if (g_code.actor[tilenum] ~= nil) then
596        pwarnprintf(pos, "redefined actor %d", tilenum)
597    end
598    g_code.actor[tilenum] = codetab
599    g_code.aflagsloc[tilenum] = getLocation("definition of actor", pos)
600end
601
602-- NOTE: in C-CON, the slash and backslash can also be part of an identifier,
603-- but this is likely to support file names in other places.
604local BAD_ID_CHARS0 = "_*?"  -- allowed 1st identifier chars
605local BAD_ID_CHARS1 = "_*-+?."  -- allowed following identifier chars
606
607local function truetab(tab)
608    local ttab = {}
609    for i=1,#tab do
610        ttab[tab[i]] = true
611    end
612    return ttab
613end
614
615-- Lua 5.2 keywords. Not 5.1 because we use "goto" for codegen.
616local LUA_KEYW = truetab {
617    "and", "break", "do", "else", "elseif", "end",
618    "false", "for", "function", "goto", "if", "in",
619    "local", "nil", "not", "or", "repeat", "return",
620    "then", "true", "until", "while"
621}
622
623-- Return the Lua code by which the CON object <name> is referenced in the
624-- translated code.
625local function mangle_name(name, prefix)
626    if (name:match("^[A-Za-z_][A-Za-z_0-9]*$") and not LUA_KEYW[name]) then
627        return format("_%s.%s", prefix, name)
628    else
629        return format("_%s[%q]", prefix, name)
630    end
631end
632
633function on.state_begin_Cmt(_subj, _pos, statename)
634    -- We must register the state name early (Cmt) because otherwise, it won't
635    -- be found in a recursive state. XXX: The real issue seems to be the use
636    -- of "Cmt"s in other places, which messes up the sequence of running the
637    -- semantic actions.
638    local ourname = mangle_name(statename, "F")
639    g_funcname[statename] = ourname
640    return true, ourname
641end
642
643function on.state_end(pos, funcname, codetab)
644    paddcodef(pos, "%s=function(_aci,_pli,_dist)", funcname)
645    addcode(get_cache_sap_code())
646    add_code_and_end(codetab, "end")
647end
648
649function on.event_end(pos, eventidx, codetab)
650    assert(type(codetab)=="table")
651    -- 0x20000000: actor.FLAGS.chain_beg
652    paddcodef(pos, "gameevent{%d,0x20000000,function(_aci,_pli,_dist)", eventidx)
653    addcode(get_cache_sap_code())
654    addcode(codetab)
655    addcode("end}")
656
657    g_code.event[eventidx] = codetab
658end
659
660function on.appendevent_end(pos, eventidx, codetab)
661    assert(type(codetab)=="table")
662    -- 0x40000000: actor.FLAGS.chain_end
663    paddcodef(pos, "gameevent{%d,0x40000000,function(_aci,_pli,_dist)", eventidx)
664    addcode(get_cache_sap_code())
665    addcode(codetab)
666    addcode("end}")
667
668    -- XXX: appendevent needs different behavior? g_code.event doesn't appear to be used anywhere, for now.
669    g_code.event[eventidx] = codetab
670end
671
672function on.eventloadactor_end(pos, tilenum, codetab)
673    if (on.fnames_tilenum_label(tilenum)) then
674        return
675    end
676
677    -- Translate eventloadactor into a chained EVENT_LOADACTOR block
678    paddcodef(pos, "gameevent{'LOADACTOR',function(_aci,_pli,_dist)")
679    addcode(get_cache_sap_code())
680    addcodef("if (%s==%d) then", SPS".picnum", tilenum)
681    addcode(codetab)
682    addcode("end")
683    addcode("end}")
684
685    if (g_code.loadactor[tilenum] ~= nil and g_warn["chained-loadactor"]) then
686        -- NOTE: C-CON redefines loadactor code if encountered multiple times.
687        pwarnprintf(pos, "chained additional loadactor %d code", tilenum)
688    end
689    g_code.loadactor[tilenum] = codetab
690end
691
692----------
693
694local function linecolstr(pos)
695    local line, col = getlinecol(pos)
696    return format("%d:%d", line, col)
697end
698
699local function increment_numerrors()
700    g_numerrors = g_numerrors+1
701    if (g_numerrors == g_maxerrors) then
702        g_numerrors = inf
703        printf("Too many errors (%d), aborting...", g_maxerrors)
704    end
705end
706
707function perrprintf(pos, fmt, ...)
708    printf("%s %s: error: "..fmt, g_filename,
709           pos and linecolstr(pos) or "???", ...)
710    increment_numerrors()
711end
712
713function errprintf(fmt, ...)
714    perrprintf(g_lastkwpos, fmt, ...)
715end
716
717function pwarnprintf(pos, fmt, ...)
718    printf("%s %s: warning: "..fmt, g_filename,
719           pos and linecolstr(pos) or "???", ...)
720end
721
722function warnprintf(fmt, ...)
723    pwarnprintf(g_lastkwpos, fmt, ...)
724end
725
726-- Print a continuation line to an error or warning.
727function contprintf(iserr, fmt, ...)
728    printf("%s %s: %s  "..fmt, g_filename,
729           g_lastkwpos and linecolstr(g_lastkwpos) or "???",
730           iserr and "     " or "       ", ...)
731end
732
733local function parse_number(pos, numstr)
734    -- <numstr> is a full number string, potentially prefixed with a minus sign.
735    local num = tonumber((numstr:gsub("h$", "")))
736--    local onum = num
737    local hex = numstr:match("0[xX]([^h]*)h?")  -- get hex digits, if any
738
739    -- num==nil for Rio Lua, which doesn't handle large hex literals.
740    if (num==nil or not (num >= -0x80000000 and num <= 0xffffffff)) then
741        -- number is <INT32_MIN or >UINT32_MAX or NaN
742        if (hex and #hex>8 and hex:sub(1,#hex-8):match("^[fF]$")) then
743            -- Too many hex digits, but they're all Fs.
744            pwarnprintf(pos, "number %s truncated to 32 bits", numstr)
745            num = bit.tobit(num)
746        else
747            perrprintf(pos, "number %s out of the range of a 32-bit integer", numstr)
748            -- Be careful not to write bound checks like
749            -- "if (i<LOWBOUND or i>HIGHBOUND) then error('...') end":
750            num = NaN
751        end
752    elseif (num >= 0x80000000) then
753        num = bit.tobit(num)
754        if (not hex and g_warn["number-conversion"]) then
755            pwarnprintf(pos, "number %s converted to %d", numstr, num)
756        end
757    end
758
759--    printf("numstr:%s, num=%d (0x%s) '%s', resnum=%d (0x%s)",
760--           numstr, onum, bit.tohex(onum), hex, num, bit.tohex(num))
761    return num
762end
763
764-- Bound checking functions that generate a compilation error on failure.
765local check = {}
766
767function check.tile_idx(tilenum)
768    if (not (tilenum >= 0 and tilenum < C.MAXTILES)) then
769        errprintf("invalid tile number %d", tilenum)
770        return false
771    end
772    return true
773end
774
775function check.sound_idx(sidx)
776    if (not (sidx >= 0 and sidx < conl.MAXSOUNDS)) then
777        errprintf("invalid sound number %d", sidx)
778        return false
779    end
780    return true
781end
782
783
784-- Mapping of various "define" types to the respective number of members and
785-- vice versa
786local LABEL = { MOVE=2, AI=3, ACTION=5, [2]="move", [3]="ai", [5]="action",
787                NUMBER=1, [1]="number" }
788
789-- Function names in the 'con' module:
790local LABEL_FUNCNAME = { [2]="move", [3]="ai", [5]="action" }
791local LABEL_PREFIX = { [2]="M", [3]="I", [5]="C" }  -- _C, _M, _I in the gen'd code
792
793local g_labeldef = {}  -- Lua numbers for numbers, strings for composites
794local g_labeltype = {}
795local g_labelspecial = {}  -- [<label>] = true
796local g_labelloc = {}  -- [<label>] = { filename, linenum, colnum }
797
798-- Get location table for use in continued warning/error reporting.
799--[[ local --]]
800function getLocation(kind, pos)
801    local loc = { g_filename, getlinecol(pos or g_lastkwpos) }
802    loc[4] = kind
803    return loc
804end
805
806function reset.labels()
807    g_badids = {}
808
809    -- NO is also a valid `move', `ai' or `action', but they are handled
810    -- separately in lookup.composite().
811    g_labeldef = {
812        NO = 0,
813        -- NOTE: these are read-only gamevars in C-CON
814        CLIPMASK0 = 65536+1,  -- blocking
815        CLIPMASK1 = (256*65536)+64,  -- hittable
816        -- TODO_MP
817        COOP = 0,
818        MULTIMODE = 1,
819        numplayers = 1,
820        myconnectindex = 0,
821        -- Predefined constants
822        MAXSTATUS = C.MAXSTATUS,
823        MAXSPRITES = C.MAXSPRITES,
824        MAX_WEAPONS = C.MAX_WEAPONS,
825    }
826
827    g_labeltype = {}
828    g_labelspecial = {}
829    g_labelloc = {}
830
831    for varname,_ in pairs(g_labeldef) do
832        g_labeltype[varname] = LABEL.NUMBER
833        g_labelspecial[varname] = true
834    end
835
836    -- Initialize default defines.
837    for i=1,#conl.labels do
838        for label, val in pairs(conl.labels[i]) do
839            g_labeldef[label] = val
840            g_labeltype[label] = LABEL.NUMBER
841        end
842    end
843end
844
845function lookup.defined_label(pos, maybe_minus_str, identifier)
846    local num = g_labeldef[identifier]
847
848    if (num == nil) then
849        perrprintf(pos, "label \"%s\" is not defined", identifier)
850        return -inf  -- return a number for type cleanness
851    end
852
853    if (g_labeltype[identifier] ~= LABEL.NUMBER) then
854        perrprintf(pos, "label \"%s\" is not a `define'd number", identifier)
855        return -inf
856    end
857
858    assert(type(num)=="number")
859
860    return (maybe_minus_str=="" and 1 or -1) * num
861end
862
863assert(not BAD_ID_CHARS1:find(":"))
864function lookup.raw_defined_label(pos, maybe_minus_str, identifier)
865    return pos..":"..maybe_minus_str..":"..identifier
866end
867
868local dynmap = {}
869-- When necessary, initialize dynamic {tile,sound} mapping list.
870function dynmap.maybe_init(dyni, dynList)
871    if (dyni[1]==nil) then
872        dyni[1] = true
873        -- Init name -> g_dyn*List index mapping
874        for i=0,math.huge do
875            local str = dynList[i].str
876            if (str==nil) then
877                break
878            end
879
880            dyni[ffi.string(str)] = i
881        end
882    end
883end
884
885-- Potentially process one dynamic {tile,sound} remapping.
886function dynmap.maybe_process(dyni, dynList, identifier, num)
887    if (dyni[identifier]) then
888        local di = dynList[dyni[identifier]]
889
890        if (ffiC._DEBUG_LUNATIC~=0 and di.staticval~=num) then
891            printf("REMAP %s (%d) --> %d", ffi.string(di.str), di.staticval, num)
892        end
893        di.dynvalptr[0] = num
894    end
895end
896
897-- The 'check' table is also used to hold a couple of misc checkers.
898
899function check.sysvar_def_attempt(identifier)
900    if (identifier=="actorvar") then
901        errprintf("cannot define reserved symbol `actorvar'")
902        return true
903    end
904    if (identifier=="_IS_NORESET_GAMEVAR") then
905        errprintf("cannot define reserved symbol `_IS_NORESET_GAMEVAR'")
906        return true
907    end
908end
909
910
911local inform = {}
912
913function inform.common(loc, iserr, prefix)
914    if (loc) then
915        contprintf(iserr, prefix.." is at %s %d:%d", loc[1], loc[2], loc[3])
916    else
917        contprintf(iserr, prefix.." is built-in")
918    end
919end
920
921function inform.olddef_location(identifier, iserr)
922    inform.common(g_labelloc[identifier], iserr, "Old definition")
923end
924
925function inform.oldgv_location(identifier, iserr)
926    inform.common(g_gamevar[identifier].loc, iserr, "Old definition")
927end
928
929function inform.gv_location(identifier, iserr)
930    inform.common(g_gamevar[identifier].loc, iserr, "Definition")
931end
932
933
934local Define = {}
935
936function Define.label(identifier, num)
937    if (check.sysvar_def_attempt(identifier)) then
938        return
939    end
940
941    local oldtype = g_labeltype[identifier]
942    local oldval = g_labeldef[identifier]
943
944    if (oldval) then
945        if (oldtype ~= LABEL.NUMBER) then
946            errprintf("Refusing to overwrite `%s' label \"%s\" with a `define'd number.",
947                      LABEL[oldtype], identifier)
948            inform.olddef_location(identifier, true)
949        else
950            -- conl.labels[...]: don't warn for wrong PROJ_ redefinitions
951            if (g_warn["not-redefined"]) then
952                if (oldval ~= num and conl.PROJ[identifier]==nil) then
953                    warnprintf("Label \"%s\" not redefined with new value %d (old: %d).",
954                               identifier, num, oldval)
955                    inform.olddef_location(identifier, false)
956                end
957            end
958        end
959    else
960        if (g_gamevar[identifier]) then
961            warnprintf("symbol `%s' already used for game variable", identifier)
962            inform.oldgv_location(identifier, false)
963        end
964
965        if (ffi and g_dyntilei and (num>=0 and num<C.MAXTILES)) then
966            dynmap.maybe_init(g_dyntilei, ffiC.g_dynTileList)
967            dynmap.maybe_process(g_dyntilei, ffiC.g_dynTileList, identifier, num)
968        end
969
970        -- New definition of a label
971        g_labeldef[identifier] = num
972        g_labeltype[identifier] = LABEL.NUMBER
973        g_labelloc[identifier] = getLocation()
974    end
975end
976
977function check.composite_literal(labeltype, pos, num)
978    if (num==0 or num==1) then
979        return (num==0) and "0" or "1"
980    else
981        perrprintf(pos, "literal `%s' number must be either 0 or 1", LABEL[labeltype])
982        return "_INVALIT"
983    end
984end
985
986function lookup.composite(labeltype, pos, identifier)
987    if (identifier=="NO") then
988        -- NO is a special case and is valid for move, action and ai,
989        -- being the same as passing a literal 0.
990        return "0"
991    end
992
993    local val = g_labeldef[identifier]
994    local typ = g_labeltype[identifier]
995
996    if (val == nil) then
997        perrprintf(pos, "label \"%s\" is not defined", identifier)
998        return "_NOTDEF"
999    elseif (typ ~= labeltype) then
1000        if (identifier=="randomangle" and labeltype==LABEL.MOVE and typ==LABEL.NUMBER) then
1001            -- Be forgiving with a 1.3/1.5 GAME.CON type error.
1002            pwarnprintf(pos, "label \"randomangle\" is not a `move' value, assuming 0")
1003            return "0"
1004        elseif (identifier=="BLIMPRESPAWNTIME" and labeltype==LABEL.ACTION and typ==LABEL.NUMBER) then
1005            -- Be forgiving with a 1.3 GAME.CON type error.
1006            pwarnprintf(pos, "label \"BLIMPRESPAWNTIME\" is not an `action' value, assuming 0")
1007            return "0"
1008        else
1009            perrprintf(pos, "label \"%s\" is not a%s `%s' value", identifier,
1010                       labeltype==LABEL.MOVE and "" or "n", LABEL[labeltype])
1011            return "_WRONGTYPE"
1012        end
1013    end
1014
1015    return val
1016end
1017
1018function check.reserved_bits(flags, allowedbits, suffix)
1019    local rbits = bit.bnot(allowedbits)
1020    if (bit.band(flags, rbits) ~= 0) then
1021        warnprintf("set one or more reserved bits (0x%s) "..suffix,
1022                   bit.tohex(bit.band(flags, rbits)))
1023    end
1024end
1025
1026-- KEEPINSYNC control.lua
1027Define.ALLOWED_VIEWTYPE = truetab { 0, 1, 2, 3,4, 5, 7, 8, -5, -7, -8 }
1028
1029function Define.composite(labeltype, identifier, ...)
1030    local oldtype = g_labeltype[identifier]
1031    local oldval = g_labeldef[identifier]
1032
1033    if (oldval) then
1034        if (oldtype ~= labeltype) then
1035            errprintf("Refusing to overwrite `%s' label \"%s\" with a `%s' value.",
1036                      LABEL[oldtype], identifier, LABEL[labeltype])
1037            inform.olddef_location(identifier, true)
1038        else
1039            warnprintf("Duplicate `%s' definition of \"%s\" ignored.",
1040                       LABEL[labeltype], identifier)
1041            inform.olddef_location(identifier, false)
1042        end
1043        return
1044    end
1045
1046    -- Fill up omitted arguments denoting composites with zeros.
1047    local isai = (labeltype == LABEL.AI)
1048    local args = {...}
1049    for i=#args+1,labeltype do
1050        -- Passing nil/nothing as remaining args to con.ai will make the
1051        -- action/move the null one.
1052        args[i] = (isai and i<=2) and "nil" or 0
1053    end
1054
1055    if (isai) then
1056        assert(type(args[1])=="string")
1057        assert(type(args[2])=="string")
1058
1059        -- OR together the flags
1060        for i=#args,LABEL.AI+1, -1 do
1061            args[LABEL.AI] = bit.bor(args[LABEL.AI], args[i])
1062            args[i] = nil
1063        end
1064
1065        -- Check whether movflags use reserved bits.
1066        check.reserved_bits(args[LABEL.AI], 4096+2047, "for ai's movflags")
1067    end
1068
1069    if (labeltype == LABEL.ACTION) then
1070        -- Sanity-check action members.
1071        -- KEEPINSYNC with ACTOR_CHECK in control.lua for consistency.
1072        if (not (args[2] >= 0)) then
1073            errprintf("action \"%s\" has negative number of frames", identifier)
1074        end
1075        if (Define.ALLOWED_VIEWTYPE[args[3]] == nil) then
1076            errprintf("action \"%s\" has disallowed viewtype %d", identifier, args[3])
1077        end
1078        if (not (args[4] >= -1 and args[4] <= 1)) then
1079            warnprintf("action \"%s\" has incval different from -1, 0 or 1", identifier)
1080        end
1081    end
1082
1083    -- Make a string out of that.
1084    for i=1+(isai and 2 or 0),#args do
1085        args[i] = format("%d", args[i])
1086    end
1087
1088    local refcode = mangle_name(identifier, LABEL_PREFIX[labeltype])
1089    addcodef(isai and "%s=_con.%s(%s)" or "%s=_con.%s{%s}",  -- ai has parens
1090             refcode, LABEL_FUNCNAME[labeltype], table.concat(args, ","))
1091
1092    g_labeldef[identifier] = refcode
1093    g_labeltype[identifier] = labeltype
1094    g_labelloc[identifier] = getLocation()
1095end
1096
1097
1098local function parse(contents) end -- fwd-decl
1099
1100local function do_include_file(dirname, filename, isroot)
1101    assert(type(filename)=="string")
1102
1103    if (g_have_file[filename] ~= nil) then
1104        printf("[%d] Fatal error: infinite loop including \"%s\"", g_recurslevel, filename)
1105        g_numerrors = inf
1106        return
1107    end
1108
1109    local contents
1110
1111    if (read_into_string) then
1112        -- running from EDuke32
1113        contents = read_into_string(filename)
1114    else
1115        -- running stand-alone
1116        local io = require("io")
1117
1118        local fd, msg = io.open(dirname..filename)
1119        while (fd == nil and not isroot and filename:find("/")) do
1120            -- strip up to and including first slash:
1121            filename = filename:gsub("^.-/", "")
1122            fd, msg = io.open(dirname..filename)
1123        end
1124
1125        -- As a last resort, try the "default directory"
1126        if (fd==nil and not isroot and g_defaultDir) then
1127            -- strip up to and including last slash (if any):
1128            filename = filename:gsub("^.*/", "")
1129            dirname = g_defaultDir.."/"
1130            fd, msg = io.open(dirname..filename)
1131        end
1132
1133        if (fd == nil) then
1134            printf("[%d] Fatal error: couldn't open %s", g_recurslevel, msg)
1135            g_numerrors = inf
1136            return
1137        end
1138
1139        contents = fd:read("*all")
1140        fd:close()
1141    end
1142
1143    if (contents == nil) then
1144        -- maybe that file name turned out to be a directory or other
1145        -- special file accidentally
1146        printf("[%d] Fatal error: couldn't read from \"%s\"",
1147               g_recurslevel, dirname..filename)
1148        g_numerrors = inf
1149        return
1150    end
1151
1152    printf("%s[%d] Translating file \"%s\"", (g_recurslevel==-1 and "\n---- ") or "",
1153           g_recurslevel+1, dirname..filename);
1154
1155    local oldfilename = g_filename
1156    g_filename = filename
1157    parse(contents)
1158    g_filename = oldfilename
1159end
1160
1161-- Table of various outer command handling functions.
1162local Cmd = {}
1163
1164function Cmd.NYI(msg)
1165    return function()
1166        errprintf(msg.." not yet implemented")
1167    end
1168end
1169
1170function Cmd.nyi(msg)
1171    return function()
1172        warnprintf(msg.." not yet implemented")
1173    end
1174end
1175
1176function Cmd.include(filename)
1177    do_include_file(g_directory, filename, false)
1178end
1179
1180--- Per-module game data
1181local g_data = {}
1182local EPMUL = conl.MAXLEVELS
1183
1184function reset.gamedata()
1185    g_data = {}
1186
1187    -- [EPMUL*ep + lev] = { ptime=<num>, dtime=<num>, fn=<str>, name=<str> }
1188    g_data.level = {}
1189    -- [ep] = <str>
1190    g_data.volname = {}
1191    -- [skillnum] = <str>
1192    g_data.skillname = {}
1193    -- [quotenum] = <str>
1194    g_data.quote = {}
1195    -- table of length 26 or 30 containg numbers
1196    g_data.startup = {}
1197    -- [soundnum] = { fn=<str>, params=<table of length 5> }
1198    g_data.sound = {}
1199    -- [volnum] = <table of length numlevels (<= MAXLEVELS) of <str>>
1200    g_data.music = {}
1201end
1202
1203-- TODO: PRE13 has no <dtstr> (3D Realms time).
1204function Cmd.definelevelname(vol, lev, fn, ptstr, dtstr, levname)
1205    if (not (vol >= 0 and vol < conl.MAXVOLUMES)) then
1206        errprintf("volume number exceeds maximum volume count.")
1207        return
1208    end
1209
1210    if (not (lev >= 0 and lev < conl.MAXLEVELS)) then
1211        errprintf("level number exceeds maximum number of levels per episode.")
1212        return
1213    end
1214
1215    -- TODO: Bcorrectfilename(fn)
1216
1217    local function secs(tstr)
1218        local m, s = string.match(tstr, ".+:.+")
1219        m, s = tonumber(m), tonumber(s)
1220        return (m and s) and m*60+s or 0
1221    end
1222
1223    local map = {
1224        ptime=secs(ptstr), dtime=secs(dtstr), fn="/"..fn, name=levname
1225    }
1226
1227    if (ffi) then
1228        ffiC.C_DefineLevelName(vol, lev, map.fn, map.ptime, map.dtime, map.name)
1229    end
1230
1231    g_data.level[EPMUL*vol+lev] = map
1232end
1233
1234function Cmd.undefinelevel(vol, lev)
1235    if (not (vol >= 0 and vol < conl.MAXVOLUMES)) then
1236        errprintf("volume number exceeds maximum volume count.")
1237        return
1238    end
1239
1240    if (not (lev >= 0 and lev < conl.MAXLEVELS)) then
1241        errprintf("level number exceeds maximum number of levels per episode.")
1242        return
1243    end
1244
1245    if (ffi) then
1246        ffiC.C_UndefineLevel(vol, lev)
1247    end
1248end
1249
1250local function defineXname(what, ffiCfuncname, X, name)
1251    if (ffi) then
1252        ffiC[ffiCfuncname](X, name)
1253        if (#name > 32) then
1254            warnprintf("%s %d name truncated to 32 characters.", what, X)
1255        end
1256    end
1257    return name
1258end
1259
1260function Cmd.defineskillname(skillnum, name)
1261    if (not (skillnum >= 0 and skillnum < conl.MAXSKILLS)) then
1262        errprintf("skill number is negative or exceeds maximum skill count.")
1263        return
1264    end
1265
1266    name = defineXname("skill", "C_DefineSkillName", skillnum, name)
1267    g_data.skillname[skillnum] = name
1268end
1269
1270function Cmd.undefineskill(skillnum)
1271    if (not (skillnum >= 0 and skillnum < conl.MAXSKILLS)) then
1272        errprintf("skill number is negative or exceeds maximum skill count.")
1273        return
1274    end
1275
1276    if (ffi) then
1277        ffiC.C_UndefineSkill(skillnum)
1278    end
1279end
1280
1281function Cmd.definevolumename(vol, name)
1282    if (not (vol >= 0 and vol < conl.MAXVOLUMES)) then
1283        errprintf("volume number is negative or exceeds maximum volume count.")
1284        return
1285    end
1286
1287    name = defineXname("volume", "C_DefineVolumeName", vol, name)
1288    g_data.volname[vol] = name
1289end
1290
1291function Cmd.definevolumeflags(vol, flags)
1292    if (not (vol >= 0 and vol < conl.MAXVOLUMES)) then
1293        errprintf("volume number is negative or exceeds maximum volume count.")
1294        return
1295    end
1296
1297    if (ffi) then
1298        ffiC.C_DefineVolumeFlags(vol, flags)
1299    end
1300end
1301
1302function Cmd.undefinevolume(vol)
1303    if (not (vol >= 0 and vol < conl.MAXVOLUMES)) then
1304        errprintf("volume number is negative or exceeds maximum volume count.")
1305        return
1306    end
1307
1308    if (ffi) then
1309        ffiC.C_UndefineVolume(vol)
1310    end
1311end
1312
1313function Cmd.definegamefuncname(idx, name)
1314    local NUMGAMEFUNCTIONS = (ffi and ffiC.NUMGAMEFUNCTIONS or 56)
1315    if (not (idx >= 0 and idx < NUMGAMEFUNCTIONS)) then
1316        errprintf("function number exceeds number of game functions.")
1317        return
1318    end
1319
1320    assert(type(name)=="string")
1321    -- XXX: in place of C-CON's "invalid character in function name" report:
1322    name = name:gsub("[^A-Za-z0-9]", "_")
1323
1324    if (ffi) then
1325        ffiC.C_DefineGameFuncName(idx, name)
1326    end
1327end
1328
1329function Cmd.definegametype(idx, flags, name)
1330    if (not (idx >= 0 and idx < conl.MAXGAMETYPES)) then
1331        errprintf("gametype number exceeds maximum gametype count.")
1332        return
1333    end
1334
1335    if (ffi) then
1336        ffiC.C_DefineGameType(idx, flags, name)
1337    end
1338end
1339
1340-- strip whitespace from front and back
1341local function stripws(str)
1342    return str:match("^%s*(.*)%s*$")
1343end
1344
1345function Cmd.definequote(qnum, quotestr)
1346    if (not (qnum >= 0 and qnum < conl.MAXQUOTES)) then
1347        errprintf("quote number is negative or exceeds limit of %d.", conl.MAXQUOTES-1)
1348        return ""
1349    end
1350
1351    quotestr = stripws(quotestr)
1352
1353    if (#quotestr >= conl.MAXQUOTELEN) then
1354        -- NOTE: Actually, C_DefineQuote takes care of this! That is,
1355        -- standalone, the string isn't truncated.
1356        warnprintf("quote %d truncated to %d characters.", qnum, conl.MAXQUOTELEN-1)
1357    end
1358
1359    if (ffi) then
1360        ffiC.C_DefineQuote(qnum, quotestr)
1361    end
1362
1363    g_data.quote[qnum] = quotestr
1364    return ""
1365end
1366
1367local PROJ = {}
1368for key, val in pairs(conl.PROJ) do
1369    -- Strip "PROJ_"
1370    PROJ[key:sub(6)] = val
1371end
1372
1373function Cmd.defineprojectile(tilenum, what, val)
1374    local ok = check.tile_idx(tilenum)
1375
1376    if (what==PROJ.WORKSLIKE) then
1377        check.reserved_bits(val, 2^21-1, "for PROJ_WORKSLIKE")
1378    elseif (what==PROJ.SOUND or what==PROJ.ISOUND or what==PROJ.BSOUND) then
1379        ok = ok and (val==-1 or check.sound_idx(val))
1380    elseif (what==PROJ.SPAWNS or what==PROJ.DECAL or what==PROJ.TRAIL) then
1381        ok = ok and (val==-1 or check.tile_idx(val))
1382    end
1383
1384    if (ffi and ok) then
1385        ffiC.C_DefineProjectile(tilenum, what, val)
1386    end
1387end
1388
1389-- <override>: override-set flags? The default is to bitwise OR with existing.
1390function Cmd.xspriteflags(tilenum, flags, override)
1391    local ok = check.tile_idx(tilenum)
1392    check.reserved_bits(flags, conl.user_sflags, "for sprite flags")
1393
1394    local loc = g_code.aflagsloc[tilenum]
1395
1396    if (override and loc ~= nil) then
1397        warnprintf("'spriteflags' after %s %d", loc[4], tilenum)
1398        contprintf(false, "at %s %d:%d", loc[1], loc[2], loc[3])
1399    end
1400
1401    -- Mark the last 'spriteflags' or 'sprite*' directive for the given actor.
1402    g_code.aflagsloc[tilenum] = getLocation(format("'%s' for actor", g_lastkw))
1403
1404    if (ffi and ok) then
1405        local tile = ffiC.g_tile[tilenum]
1406        tile._flags = bit.bor(override and 0 or tile._flags, flags)
1407    end
1408end
1409
1410function Cmd.precache(tilenum0, tilenum1, flagnum)
1411    local ok = check.tile_idx(tilenum0) and check.tile_idx(tilenum1)
1412
1413    if (ffi and ok) then
1414        local tile = ffiC.g_tile[tilenum0]
1415        tile._cacherange = tilenum1;
1416        if (flagnum) then
1417            tile._flags = bit.bor(tile._flags, conl.SFLAG.SFLAG_CACHE)
1418        end
1419    end
1420end
1421
1422function Cmd.cheatkeys(sc1, sc2)
1423    if (ffi) then
1424        ffiC.CheatKeys[0] = sc1
1425        ffiC.CheatKeys[1] = sc2
1426    end
1427end
1428
1429function Cmd.setdefname(filename)
1430    assert(type(filename)=="string")
1431    if (ffi) then
1432        if (ffiC.C_SetDefName(filename) ~= 0) then
1433            error("OUT OF MEMORY", 0)
1434        end
1435    end
1436end
1437
1438function Cmd.setcfgname(filename)
1439    assert(type(filename)=="string")
1440    if (ffi) then
1441        ffiC.C_SetCfgName(filename)
1442    end
1443end
1444
1445function Cmd.gamestartup(...)
1446    local args = {...}
1447
1448    -- TODO: PRE13: detection of other g_scriptVersion.
1449    if (#args ~= 26 and #args ~= 30) then
1450        errprintf("must pass either 26 (1.3D) or 30 (1.5) values")
1451        return
1452    end
1453
1454    if (ffi) then
1455        -- running from EDuke32
1456        if (#args == 30) then
1457            ffiC.g_scriptVersion = 14
1458        end
1459        local params = ffi.new("int32_t [30]", args)
1460        ffiC.G_DoGameStartup(params)
1461    end
1462
1463    g_data.startup = args  -- TODO: sanity-check them
1464end
1465
1466function Cmd.definesound(sndlabel, fn, ...)
1467    local sndnum
1468
1469    if (type(sndlabel)=="string") then
1470        -- HANDLE_RAWDEFINE
1471        local pos, minus, label = sndlabel:match("(.-):(.-):(.+)")
1472        sndnum = lookup.defined_label(tonumber(pos), minus, label)
1473
1474        if (ffi and g_dynsoundi and (sndnum>=0 and sndnum<conl.MAXSOUNDS)) then
1475            dynmap.maybe_init(g_dynsoundi, ffiC.g_dynSoundList)
1476            dynmap.maybe_process(g_dynsoundi, ffiC.g_dynSoundList, label, sndnum)
1477        end
1478    else
1479        assert(type(sndlabel)=="number")
1480        sndnum = sndlabel
1481    end
1482
1483    if (not (sndnum >= 0 and sndnum < conl.MAXSOUNDS)) then
1484        errprintf("sound number is negative or exceeds sound limit of %d", conl.MAXSOUNDS-1)
1485        return
1486    end
1487
1488    local params = {...}  -- TODO: sanity-check them some more
1489    check.reserved_bits(params[4], 31+128, "for sound flags")
1490
1491    if (ffi) then
1492        local cparams = ffi.new("int32_t [5]", params)
1493        assert(type(fn)=="string")
1494        ffiC.C_DefineSound(sndnum, fn, cparams)
1495    end
1496
1497    g_data.sound[sndnum] = { fn=fn, params=params }
1498end
1499
1500function Cmd.music(volnum, ...)
1501    if (not (volnum >= 0 and volnum <= conl.MAXVOLUMES+1)) then
1502        -- The passed volume number is 1-based.
1503        -- Both 0 and MAXVOLUMES+1 means "special music"
1504        errprintf("volume number must be between 0 and MAXVOLUMES+1=%d", conl.MAXVOLUMES+1)
1505        return
1506    elseif (volnum == conl.MAXVOLUMES+1) then
1507        warnprintf("volume number MAXVOLUMES+1 is discouraged, use 0 instead")
1508    end
1509
1510    if (volnum == 0) then
1511        volnum = conl.MAXVOLUMES+1  -- special music
1512    end
1513
1514    local filenames = {...}
1515    local MAXFNS = conl.MAXLEVELS
1516
1517    if (#filenames > MAXFNS) then
1518        warnprintf("ignoring extraneous %d music file names", #filenames-MAXFNS)
1519        for i=MAXFNS+1,#filenames do
1520            filenames[i] = nil
1521        end
1522    end
1523
1524    if (ffi) then
1525        for i=1,#filenames do
1526            assert(type(filenames[i])=="string")
1527            ffiC.C_DefineMusic(volnum-1, i-1, "/"..filenames[i])
1528        end
1529    end
1530
1531    g_data.music[volnum] = filenames
1532end
1533
1534
1535--- GAMEVARS / GAMEARRAYS
1536
1537function Cmd.gamearray(identifier, initsize)
1538    if (check.sysvar_def_attempt(identifier)) then
1539        return
1540    end
1541
1542    if (not (initsize >= 0 and initsize < 0x7fffffff)) then
1543        errprintf("invalid initial size %d for gamearray `%s'", initsize, identifier)
1544        return
1545    end
1546
1547    local oga = g_gamearray[identifier]
1548    if (oga) then
1549        if (oga.sysp) then
1550            errprintf("attempt to define system gamearray `%s'", identifier)
1551            return
1552        elseif (initsize ~= oga.size) then
1553            errprintf("duplicate gamearray definition `%s' has different size", identifier)
1554            return
1555        else
1556            warnprintf("duplicate gamearray definition `%s' ignored", identifier)
1557            return
1558        end
1559    end
1560
1561    if (g_gamevar[identifier]) then
1562        warnprintf("symbol `%s' already used for game variable", identifier)
1563        inform.oldgv_location(identifier, false)
1564    end
1565
1566    local ga = { name=mangle_name(identifier, "A"), size=initsize }
1567    g_gamearray[identifier] = ga
1568
1569    addcode("if _S then")
1570    addcodef("%s=_con._gamearray(%d)", ga.name, initsize)
1571    addcode("end")
1572end
1573
1574function Cmd.gamevar(identifier, initval, flags)
1575    if (check.sysvar_def_attempt(identifier)) then
1576        return
1577    end
1578
1579    if (bit.band(flags, bit.bnot(GVFLAG.USER_MASK)) ~= 0) then
1580        -- TODO: a couple of the presumably safe ones
1581        errprintf("gamevar flags other than 1, 2, 1024 or 131072: NYI or forbidden")
1582        return
1583    end
1584
1585    local perPlayer = (bit.band(flags, GVFLAG.PERPLAYER) ~= 0)
1586    local perActor = (bit.band(flags, GVFLAG.PERACTOR) ~= 0)
1587
1588    if (perPlayer and perActor) then
1589        errprintf("invalid gamevar flags: must be either PERPLAYER or PERACTOR, not both")
1590        return
1591    end
1592
1593    local ogv = g_gamevar[identifier]
1594    -- handle NORESET or NODEFAULT
1595    local isSessionVar = (bit.band(flags, GVFLAG.NODEFAULT) ~= 0)
1596    local storeWithSavegames = (bit.band(flags, GVFLAG.NORESET) == 0)
1597
1598    local actorVarSuffix = ""
1599
1600    if (isSessionVar and (perPlayer or perActor)) then
1601        if (perActor) then
1602            actorVarSuffix = ",nil,true"
1603--            flags = bit.band(flags, bit.bnot(GVFLAG.NODEFAULT))
1604            isSessionVar = false
1605        elseif (perPlayer) then
1606            flags = bit.band(flags, bit.bnot(GVFLAG.PERPLAYER))
1607            perPlayer = false
1608
1609            if (ogv == nil) then  -- warn only once per gamevar
1610                warnprintf("per-player session gamevar `%s': NYI, made global", identifier)
1611            end
1612        end
1613    end
1614
1615    if (ogv ~= nil) then
1616        local oflags = bit.band(ogv.flags, bit.bnot(GVFLAG.CON_PERPLAYER))
1617
1618        if (oflags ~= flags) then
1619            if (bit.band(oflags, GVFLAG.SYSTEM) ~= 0 and not isSessionVar) then
1620                -- Attempt to override a system gamevar. See if it's read-only...
1621                if (bit.band(oflags, GVFLAG.READONLY) ~= 0) then
1622                    errprintf("attempt to override read-only system gamevar `%s'", identifier)
1623                    return
1624                end
1625
1626                local flagsnosys = bit.band(oflags, bit.bnot(GVFLAG.SYSTEM))
1627                if (flagsnosys ~= flags and g_warn["system-gamevar"]) then
1628                    warnprintf("overrode initial value of `%s', but kept "..
1629                               "flags (%d)", identifier, flagsnosys)
1630                end
1631
1632                if (ogv.rbits and bit.band(ogv.rbits, initval)~=0) then
1633                    warnprintf("set one or more reserved bits (0x%s) in overriding `%s'",
1634                               bit.tohex(bit.band(ogv.rbits, initval)), identifier)
1635                end
1636
1637                local linestr = "--"..getlinecol(g_lastkwpos)
1638
1639                -- Emit code to set the variable at Lua parse time.
1640                -- XXX: How does this interact with savegame restoration?
1641                if (bit.band(oflags, GVFLAG.PERPLAYER) ~= 0) then
1642                    -- Replace player index by 0. PLAYER_0.
1643                    -- TODO_MP: init for all players.
1644                    local pvar, numrepls = ogv.name:gsub("_pli", "0")
1645                    assert(numrepls>=1)
1646                    addcodef("%s=%d%s", pvar, initval, linestr)
1647                else
1648                    addcodef("%s=%d%s", ogv.name, initval, linestr)
1649                end
1650                return
1651            end
1652
1653            errprintf("duplicate definition of gamevar `%s' has different flags (new: %x, old: %x)", identifier, flags, oflags)
1654            inform.oldgv_location(identifier, true)
1655            return
1656        else
1657            warnprintf("duplicate definition of gamevar `%s' ignored", identifier)
1658            inform.oldgv_location(identifier, false)
1659            return
1660        end
1661    end
1662
1663    local ltype = g_labeltype[identifier]
1664    if (ltype ~= nil) then
1665        warnprintf("Symbol `%s' already used for a defined %s.", identifier, LABEL[ltype])
1666        inform.olddef_location(identifier, false)
1667    end
1668
1669    if (isSessionVar) then
1670        if (g_numSessionVars == conl.MAXSESSIONVARS) then
1671            errprintf("Declared too many session gamevars (flag 1024), can have at most %d.",
1672                      conl.MAXSESSIONVARS)
1673            return
1674        end
1675
1676        -- Declare new session gamevar.
1677        local gv = { name=format("_gv._sessionVar[%d]", g_numSessionVars),
1678                     flags=flags, loc=getLocation(), used=0 }
1679        g_numSessionVars = g_numSessionVars+1
1680
1681        g_gamevar[identifier] = gv;
1682        -- Initialize it (i.e. set to the declared initial value) on first run,
1683        -- but not from savegames.
1684        addcodef("if _S then %s=%d end", gv.name, initval)
1685
1686        return
1687    end
1688
1689    local gv = { name=mangle_name(identifier, "V"), flags=flags, loc=getLocation(), used=0 }
1690    g_gamevar[identifier] = gv
1691
1692    if (storeWithSavegames) then
1693        addcode("if _S then")
1694    end
1695
1696    if (perActor) then
1697        addcodef("%s=_con.actorvar(%d%s)", gv.name, initval, actorVarSuffix)
1698    elseif (perPlayer and g_cgopt["playervar"]) then
1699        gv.flags = bit.bor(gv.flags, GVFLAG.CON_PERPLAYER)
1700        addcodef("%s=_con.playervar(%d)", gv.name, initval)
1701    else
1702        addcodef("%s=%d", gv.name, initval)
1703    end
1704
1705    if (storeWithSavegames) then
1706        addcode("end")
1707    end
1708end
1709
1710function Cmd.dynamicremap()
1711    if (g_dyntilei==nil) then
1712        print("Using dynamic tile remapping");
1713        g_dyntilei = {};
1714    end
1715end
1716
1717function Cmd.dynamicsoundremap()
1718    if (g_dynsoundi==nil) then
1719        print("Using dynamic sound remapping");
1720        g_dynsoundi = {};
1721    end
1722end
1723
1724function lookup.gamearray(identifier)
1725    local ga = g_gamearray[identifier]
1726    if (ga == nil) then
1727        errprintf("symbol `%s' is not a game array", identifier)
1728        return "_INVALIDGA"
1729    end
1730    return ga.name
1731end
1732
1733local function thisactor_to_pli(var)
1734    return (var=="_aci") and "_pli" or var
1735end
1736
1737function lookup.error_not_gamevar(identifier)
1738    errprintf("symbol `%s' is not a game variable", identifier)
1739    return "_INVALIDGV"
1740end
1741
1742-- <aorpvar>: code for actor or player index
1743function lookup.gamevar(identifier, aorpvar, writable)
1744    local gv = g_gamevar[identifier]
1745
1746    if (gv == nil) then
1747        return lookup.error_not_gamevar(identifier)
1748    end
1749
1750    if (writable and bit.band(gv.flags, GVFLAG.READONLY) ~= 0) then
1751        errprintf("gamevar `%s' is read-only", identifier)
1752        return "_READONLYGV"
1753    end
1754
1755    gv.used = bit.bor(gv.used, writable and 2 or 1)
1756
1757    if (bit.band(gv.flags, GVFLAG.PERACTOR)~=0) then
1758        return format("%s[%s]", gv.name, aorpvar)
1759    elseif (bit.band(gv.flags, GVFLAG.CON_PERPLAYER)~=0 and g_cgopt["playervar"]) then
1760        return format("%s[%s]", gv.name, thisactor_to_pli(aorpvar))
1761    else
1762        return gv.name
1763    end
1764end
1765
1766local function maybe_gamevar_Cmt(subj, pos, identifier)
1767    if (g_gamevar[identifier]) then
1768        return true, lookup.gamevar(identifier, "_aci", false)
1769    end
1770end
1771
1772
1773----==== patterns ====----
1774
1775---- basic ones
1776-- Windows, *nix and Mac newlines all exist in the wild!
1777local newline = "\r"*Pat("\n")^-1 + "\n"
1778local EOF = Pat(-1)
1779local anychar = Pat(1)
1780-- comments
1781local comment = "/*" * match_until(anychar, "*/") * "*/"
1782local linecomment = "//" * match_until(anychar, newline)
1783local whitespace = Var("whitespace")
1784local sp0 = whitespace^0
1785-- This "WS+" pattern matches EOF too, so that a forgotten newline at EOF is
1786-- properly handled
1787local sp1 = whitespace^1 + EOF
1788local alpha = Range("AZ", "az")  -- locale?
1789local alphanum = alpha + Range("09")
1790--local alnumtok = alphanum + Set("{}/\\*-_.")  -- see isaltok() in gamedef.c
1791
1792--- Basic lexical elements ("tokens"). See the final grammar ("Grammar") for
1793--- their definitions.
1794local tok =
1795{
1796    maybe_minus = (Pat("-") * sp0)^-1,
1797    number = Var("t_number"),
1798
1799    -- Valid identifier names are disjoint from keywords!
1800    -- XXX: CON is more permissive with identifier name characters:
1801    identifier = Var("t_identifier"),
1802    -- This one matches keywords, too:
1803    identifier_all = Var("t_identifier_all"),
1804
1805    define = Var("t_define"),
1806    rawdefine = Var("t_rawdefine"),
1807    actordefine = g_cgopt["names"] and Var("t_rawdefine") or Var("t_define"),
1808
1809    move = Var("t_move"),
1810    ai = Var("t_ai"),
1811    action = Var("t_action"),
1812
1813    -- NOTE: no chance to whitespace and double quotes in filenames:
1814    filename = lpeg.C((anychar-Set(" \t\r\n\""))^1),
1815    newline_term_str = match_until(anychar, newline),
1816
1817    rvar = Var("t_rvar"),
1818    wvar = Var("t_wvar"),
1819    gamearray = Var("t_gamearray"),
1820
1821    -- for definelevelname
1822    time = lpeg.C(alphanum*alphanum^-1*":"*alphanum*alphanum^-1),
1823
1824    state_ends = Pat("ends")
1825        + POS() * "else" * sp1 * "ends"
1826        / function(pos) pwarnprintf(pos, "stray `else' at end of state") end,
1827}
1828
1829
1830---- helper patterns / pattern constructing functions
1831local maybe_quoted_filename = ('"' * tok.filename * '"' + tok.filename)
1832-- empty string is handled too; we must not eat the newline then!
1833local newline_term_string = (#newline + EOF)*lpeg.Cc("")
1834    + (whitespace-newline)^1 * lpeg.C(tok.newline_term_str)
1835
1836
1837-- (sp1 * tok.define) repeated exactly n times
1838local function n_defines(n)  -- works well only for small n
1839    local pat = Pat(true)
1840    for i=1,n do
1841        pat = sp1 * tok.define * pat
1842    end
1843    return pat
1844end
1845
1846
1847local D, R, W, I, GARI, AC, MV, AI = -1, -2, -3, -4, -5, -6, -7, -8
1848local TOKEN_PATTERN = { [D]=tok.define, [R]=tok.rvar, [W]=tok.wvar,
1849                        [I]=tok.identifier, [GARI]=tok.gamearray,
1850                        [AC]=tok.action, [MV]=tok.move, [AI]=tok.ai }
1851
1852-- Generic command pattern, types given by varargs.
1853-- The command name to be matched is attached later.
1854-- Example:
1855--  "command" writtenvar readvar def def:  gencmd(W,R,D,D)
1856--    -->  sp1 * tok.wvar * sp1 * tok.rvar * sp1 * tok.define * sp1 * tok.define
1857--  "command_with_no_args":  gencmd()
1858--    --> Pat(true)
1859local function cmd(...)
1860    local pat = Pat(true)
1861    local vartypes = {...}
1862
1863    for i=1,#vartypes do
1864        pat = pat * sp1 * assert(TOKEN_PATTERN[vartypes[i]])
1865    end
1866
1867    return pat
1868end
1869
1870
1871-- The command names will be attached to the front of the patterns later!
1872
1873--== Top level CON commands ==--
1874-- XXX: many of these are also allowed inside actors/states/events in CON.
1875local Couter = {
1876    --- 1. Preprocessor
1877    include = sp1 * maybe_quoted_filename
1878        / Cmd.include,
1879    includedefault = cmd()
1880        / Cmd.NYI("`includedefault'"),
1881    define = cmd(I,D)
1882        / Define.label,
1883
1884    --- 2. Defines and Meta-Settings
1885    dynamicremap = cmd()
1886        / Cmd.dynamicremap,
1887    dynamicsoundremap = cmd()
1888        / Cmd.dynamicsoundremap,
1889    setcfgname = sp1 * tok.filename
1890        / Cmd.setcfgname,
1891    setdefname = sp1 * tok.filename
1892        / Cmd.setdefname,
1893    setgamename = newline_term_string
1894        / Cmd.nyi("`setgamename'"),
1895
1896    precache = cmd(D,D,D)
1897        / Cmd.precache,
1898    scriptsize = cmd(D)
1899        / "",  -- no-op
1900    cheatkeys = cmd(D,D)
1901        / Cmd.cheatkeys,
1902
1903    definecheat = newline_term_string  -- XXX: actually tricker syntax (TS)
1904        , -- / Cmd.nyi("`definecheat'"),
1905    definegamefuncname = sp1 * tok.define * newline_term_string  -- XXX: TS?
1906        / Cmd.definegamefuncname,
1907    definegametype = n_defines(2) * newline_term_string
1908        / Cmd.definegametype,
1909    definelevelname = n_defines(2) * sp1 * tok.filename * sp1 * tok.time * sp1 * tok.time *
1910        newline_term_string
1911        / Cmd.definelevelname,
1912    defineskillname = sp1 * tok.define * newline_term_string
1913        / Cmd.defineskillname,
1914    definevolumename = sp1 * tok.define * newline_term_string
1915        / Cmd.definevolumename,
1916
1917    definequote = sp1 * tok.define * newline_term_string
1918        / Cmd.definequote,
1919    defineprojectile = cmd(D,D,D)
1920        / Cmd.defineprojectile,
1921    definesound = sp1 * tok.rawdefine * sp1 * maybe_quoted_filename * n_defines(5)
1922        / Cmd.definesound,
1923
1924    -- NOTE: gamevar.ogg and the like is OK, too
1925    music = sp1 * tok.define * match_until(sp1 * tok.filename, sp1 * conl.keyword * sp1)
1926        / Cmd.music,
1927
1928    definevolumeflags = cmd(D,D)
1929        / Cmd.definevolumeflags,
1930
1931    undefinelevel = cmd(D,D)
1932        / Cmd.undefinelevel,
1933    undefineskill = cmd(D)
1934        / Cmd.undefineskill,
1935    undefinevolume = cmd(D)
1936        / Cmd.undefinevolume,
1937
1938    --- 3. Game Settings
1939    -- gamestartup has 26/30 fixed defines, depending on 1.3D/1.5 version:
1940    gamestartup = (sp1 * tok.define)^26
1941        / Cmd.gamestartup,
1942    spritenopal = cmd(D)
1943        / function(tilenum, flags) Cmd.xspriteflags(tilenum, conl.SFLAG.SFLAG_NOPAL) end,
1944    spritenoshade = cmd(D)
1945        / function(tilenum, flags) Cmd.xspriteflags(tilenum, conl.SFLAG.SFLAG_NOSHADE) end,
1946    spritenvg = cmd(D)
1947        / function(tilenum, flags) Cmd.xspriteflags(tilenum, conl.SFLAG.SFLAG_NVG) end,
1948    spriteshadow = cmd(D)
1949        / function(tilenum, flags) Cmd.xspriteflags(tilenum, conl.SFLAG.SFLAG_SHADOW) end,
1950
1951    spriteflags = (sp1 * tok.define)^2  -- also see inner
1952        / function(tilenum, ...) Cmd.xspriteflags(tilenum, bit.bor(...), true) end,
1953
1954    --- 4. Game Variables / Arrays
1955    gamevar = cmd(I,D,D)
1956        / Cmd.gamevar,
1957    gamearray = cmd(I,D)
1958        / Cmd.gamearray,
1959
1960    --- 5. Top level commands that are also run-time commands
1961    move = sp1 * tok.identifier * (sp1 * tok.define)^-2  -- hvel, vvel
1962        / function(...) Define.composite(LABEL.MOVE, ...) end,
1963
1964    -- startframe, numframes, viewtype, incval, delay, flags:
1965    action = sp1 * tok.identifier * (sp1 * tok.define)^-6 -- ACTION_PARAM_COUNT
1966        / function(...) Define.composite(LABEL.ACTION, ...) end,
1967
1968    -- action, move, flags...:
1969    ai = sp1 * tok.identifier * (sp1 * tok.action *
1970                                 (sp1 * tok.move * (sp1 * tok.define)^0)^-1
1971                                )^-1
1972        / function(...) Define.composite(LABEL.AI, ...) end,
1973
1974    --- 6. Deprecated TLCs
1975    betaname = newline_term_string,
1976    enhanced = cmd(D),
1977}
1978
1979
1980--== Run time CON commands ==--
1981--- 1. Gamevar Operators
1982local Op = {}
1983Op.var = cmd(W,D)
1984Op.varvar = cmd(W,R)
1985
1986function Op.var_common(thecmd, defaultop, trapop, wrapop)
1987    local theop =
1988        g_cgopt["trapv"] and trapop or
1989        g_cgopt["wrapv"] and wrapop or
1990        assert(defaultop)
1991
1992    if (#theop <= 2) then
1993        return thecmd / ("%1=%1"..theop.."%2")
1994    else
1995        return thecmd / ("%1="..theop.."(%1,%2)")
1996    end
1997end
1998
1999function Op.varf(...)
2000    return Op.var_common(Op.var, ...)
2001end
2002
2003function Op.varvarf(...)
2004    return Op.var_common(Op.varvar, ...)
2005end
2006
2007-- Allow nesting... stuff like
2008--   ifvarl actorvar[sprite[THISACTOR].owner].burning 0
2009-- is kinda breaking the classic "no array nesting" rules
2010-- (if there ever were any) but making our life harder else.
2011local arraypat = sp0 * "[" * sp0 * tok.rvar * sp0 * "]"
2012-- For {get,set}userdef:
2013local arraypat_maybe_empty = sp0 * "[" * sp0 * (tok.rvar * sp0)^-1 * "]"
2014
2015-- Table of various patterns that are (parts of) more complex inner commands.
2016local patt = {}
2017
2018-- Have to bite the bullet here and list actor/player members with second
2019-- parameters, even though it's ugly to make it part of the syntax.  Also,
2020-- stuff like
2021--   actor[xxx].loogiex parm2 x
2022-- will be wrongly accepted at the parsing stage (loogiex is player's member)
2023-- because we don't discriminate between actor and player here.
2024patt.parm2member = lpeg.C(Pat("htg_t") + "loogiex" + "loogiey" + "ammo_amount" +
2025                          "weaprecs" + "gotweapon" + "pals" + "Pals" + "max_ammo_amount") * sp1 * tok.rvar
2026-- XXX: "pals" + "Pals": this sucks! It means that we for this list of members
2027-- requiring second parameters, we will have to enumerate all lower/uppercase
2028-- instances encountered in the wild.
2029
2030-- The member name must match keywords, too (_all), because e.g. cstat is a
2031-- member of sprite[].
2032patt.bothmember = sp0 * "." * sp0 * lpeg.Ct(patt.parm2member + tok.identifier_all)
2033patt.singlemember = sp0 * "." * sp0 * tok.identifier_all
2034
2035patt.cmdgetstruct =  -- get<structname>[<idx>].<member> (<parm2>)? <<var>>
2036    arraypat * patt.bothmember * sp1 * tok.wvar
2037
2038patt.cmdsetstruct =  -- set<structname>[<idx>].<<member>> (<parm2>)? <var>
2039    arraypat * patt.bothmember * sp1 * tok.rvar
2040
2041patt.cmdgetperxvar =  -- get<actor/player>var[<idx>].<varname> <<var>>
2042    arraypat * patt.singlemember * sp1 * tok.wvar
2043
2044patt.cmdsetperxvar = -- set<actor/player>var[<idx>].<<varname>> <var>
2045    arraypat * patt.singlemember * sp1 * tok.rvar
2046
2047-- Function generating code for a struct read/write access.
2048local function StructAccess(Structname, writep, index, membertab)
2049    assert(type(membertab)=="table")
2050    -- Lowercase the member name for CON compatibility
2051    local member, parm2 = membertab[1]:lower(), membertab[2]
2052
2053    local MemberCode = conl.StructAccessCode[Structname] or conl.StructAccessCode2[Structname]
2054    -- Look up array+member name first, e.g. "spriteext[%s].angoff".
2055    local armembcode = MemberCode[member]
2056    if (armembcode == nil) then
2057        errprintf("%s: invalid %s member `.%s'", g_lastkw, Structname, member)
2058        return "_MEMBINVALID"
2059    end
2060
2061    -- Function checking a literal number for being OK for assignment to this
2062    -- member. Can also be a table {min, max}. See con_lang.lua, LITERAL_CHECKING.
2063    local lit_ok_func_or_table
2064
2065    if (type(armembcode)=="table") then
2066        -- Read and write accesses differ.
2067        if (writep) then
2068            lit_ok_func_or_table = armembcode[3]
2069        end
2070        armembcode = armembcode[writep and 2 or 1]
2071        if (armembcode==nil) then
2072            errprintf("%s access to %s[].%s is not available",
2073                      writep and "write" or "read", Structname, member)
2074            return "_MEMBNOACCESS"
2075        end
2076    end
2077
2078    if (Structname~="userdef") then
2079        -- Count number of parameters ("%s"), don't count "%%s".
2080        local _, numparms = armembcode:gsub("[^%%]%%s", "", 2)
2081        if (#membertab ~= numparms) then
2082            local nums = { "one", "two" }
2083            errprintf("%s[].%s has %s parameter%s, but %s given", Structname,
2084                      member, nums[numparms], numparms==1 and "" or "s",
2085                      nums[#membertab])
2086            return "_MEMBINVPARM"
2087        end
2088    end
2089
2090    -- THISACTOR special meanings
2091    if (Structname=="player" or Structname=="input") then
2092        index = thisactor_to_pli(index)
2093    elseif (Structname=="sector") then
2094        if (index=="_aci") then
2095            index = SPS".sectnum"
2096        end
2097    end
2098
2099    -- METHOD_MEMBER
2100    local ismethod = (armembcode:find("%%s",1,true)~=nil)
2101    -- If ismethod is true, then the formatted string will now have an "%s"
2102    local code
2103
2104    if (Structname=="userdef") then
2105--        assert(index==nil)
2106        assert(parm2==nil)
2107        code = format(armembcode, parm2)
2108    else
2109        code = format(armembcode, index, parm2)
2110    end
2111
2112    if (csapp()) then
2113        if (Structname=="player") then
2114            code = code:gsub("^player%[_pli%]", "_ps")
2115        elseif (Structname=="sprite") then
2116            code = code:gsub("^actor%[_aci%]", "_a")
2117            code = code:gsub("^sprite%[_aci%]", "_spr")
2118        end
2119    end
2120
2121    return code, ismethod, lit_ok_func_or_table
2122end
2123
2124function lookup.array_expr(writep, structname, index, membertab)
2125    if (conl.StructAccessCode[structname] == nil) then
2126        -- Try a gamearray
2127        local ganame = g_gamearray[structname] and lookup.gamearray(structname)
2128        if (ganame == nil) then
2129            if (structname=="actorvar") then
2130                -- actorvar[] inline array expr
2131                -- XXX: kind of CODEDUP with GetOrSetPerxvarCmd() factory
2132                local gv = g_gamevar[structname]
2133                if (gv and bit.band(gv.flags, GVFLAG.PERX_MASK)~=GVFLAG.PERACTOR) then
2134                    errprintf("gamevar `%s' is not per-actor", structname, "actor")
2135                    -- TODO: inform.gv_location()?
2136                end
2137
2138                if (membertab == nil) then
2139                    errprintf("actorvar[] requires a pseudo member (gamevar) name")
2140                    return "_INVALIDAV"
2141                end
2142
2143                if (#membertab > 1) then
2144                    errprintf("actorvar[] cannot be used with a second parameter")
2145                    return "_INVALIDAV"
2146                end
2147
2148                if (gv) then
2149                    gv.used = bit.bor(gv.used, writep and 2 or 1)
2150                end
2151
2152                assert(#membertab == 1)
2153                return lookup.gamevar(membertab[1], index, writep)
2154            end
2155
2156            errprintf("symbol `%s' is neither a struct nor a gamearray", structname)
2157            return "_INVALIDAR"
2158        end
2159
2160        if (membertab ~= nil) then
2161            errprintf("gamearrays cannot be indexed with member names")
2162            return "_INVALIDAR"
2163        end
2164
2165        assert(type(ganame)=="string")
2166        return format("%s[%s]", ganame, index)
2167    end
2168
2169    local membercode, ismethod = StructAccess(structname, writep, index, membertab)
2170    -- Written METHOD_MEMBER syntax not supported as "qwe:method(asd) = val"
2171    -- isn't valid Lua syntax.
2172    assert(not (writep and ismethod))
2173    return membercode
2174end
2175
2176local Access =
2177{
2178    sector = function(...) return StructAccess("sector", ...) end,
2179    wall = function(...) return StructAccess("wall", ...) end,
2180    xsprite = function(...) return StructAccess("sprite", ...) end,
2181    player = function(...) return StructAccess("player", ...) end,
2182
2183    tspr = function(...) return StructAccess("tspr", ...) end,
2184    projectile = function(...) return StructAccess("projectile", ...) end,
2185    thisprojectile = function(...) return StructAccess("thisprojectile", ...) end,
2186    userdef = function(...) return StructAccess("userdef", ...) end,
2187    input = function(...) return StructAccess("input", ...) end,
2188}
2189
2190local function GetStructCmd(accessfunc, pattern)
2191    return (pattern or patt.cmdgetstruct) /
2192      function(idx, memb, var)
2193        return format("%s=%s", var, accessfunc(false, idx, memb))
2194      end
2195end
2196
2197local function SetStructCmd(accessfunc, pattern)
2198    local function capfunc(idx, memb, var)
2199        -- litok: function or table
2200        local membercode, ismethod, litok = accessfunc(true, idx, memb)
2201
2202        -- Light static checking for literal values being OK for member
2203        -- assignment. LITERAL_CHECKING.
2204        if (type(var)=="number" and litok) then
2205            if (type(litok)=="table" and not (var>=litok[1] and var<=litok[2]) or
2206                    type(litok)=="function" and not litok(var)) then
2207                local member = memb[1]:lower()
2208                warnprintf("setting member '.%s' to %d will fail at game time",
2209                           member, var)
2210            end
2211        end
2212
2213        if (ismethod) then
2214            -- METHOD_MEMBER syntax
2215
2216            -- BE EXTRA CAREFUL! We must be sure that percent characters have
2217            -- not been smuggled into the member code string via variable names
2218            -- etc.
2219            local _, numpercents = membercode:gsub("%%", "", 2)
2220            assert(numpercents==1)
2221
2222            return format(membercode, var)
2223        else
2224            return format("%s=%s", membercode, var)
2225        end
2226    end
2227
2228    return (pattern or patt.cmdsetstruct) / capfunc
2229end
2230
2231-- <Setp>: whether the perxvar is set
2232local function GetOrSetPerxvarCmd(Setp, Actorp)
2233    local EXPECTED_PERX_BIT = Actorp and GVFLAG.PERACTOR or GVFLAG.PERPLAYER
2234    local pattern = (Setp and patt.cmdsetperxvar or patt.cmdgetperxvar)
2235
2236    local function capfunc(idx, perxvarname, var)
2237        local gv = g_gamevar[perxvarname]
2238        if (gv and bit.band(gv.flags, GVFLAG.PERX_MASK)~=EXPECTED_PERX_BIT) then
2239            -- [gs]set*var for wrong gamevar type. See if it's a getactorvar,
2240            -- in which case we may only warn and access that instead. Note
2241            -- that accesses of player gamevars with actor indices are usually
2242            -- meaningless.
2243            local warnp = not Setp and Actorp and not g_warn["error-bad-getactorvar"]
2244            local xprintf = warnp and warnprintf or errprintf
2245
2246            xprintf("gamevar `%s' is not per-%s", perxvarname, Actorp and "actor" or "player")
2247            inform.gv_location(perxvarname, not warnp)
2248
2249            if (warnp and bit.band(gv.flags, GVFLAG.PERX_MASK)==GVFLAG.PERPLAYER
2250                    and g_cgopt["bad-getactorvar-use-pli"]) then
2251                -- For getactorvar[] accesses to per-player gamevars, if
2252                -- -fbad-getactorvar-use-pli is provided, use current player
2253                -- index, for compatibility with CON.
2254                idx = "_pli"
2255            end
2256        end
2257
2258        if (not Actorp) then
2259            -- THISACTOR -> player index for {g,s}etplayervar
2260            idx = thisactor_to_pli(idx)
2261        end
2262
2263        if (gv) then
2264            gv.used = bit.bor(gv.used, Setp and 2 or 1)
2265        end
2266
2267        if (Setp) then
2268            return format("%s=%s", lookup.gamevar(perxvarname, idx, true), var)
2269        else
2270            return format("%s=%s", var, lookup.gamevar(perxvarname, idx, false))
2271        end
2272    end
2273
2274    return pattern / capfunc
2275end
2276
2277
2278local function n_s_fmt(n)
2279    return string.rep("%s,", n-1).."%s"
2280end
2281
2282-- Various inner command handling functions / string capture strings.
2283local handle =
2284{
2285    NYI = function()
2286        errprintf("command `%s' not yet implemented", g_lastkw)
2287        return ""
2288    end,
2289
2290    dynNYI = function()
2291        return format([[print(%q..":%d: `%s' not yet implemented")]],
2292                      g_filename, getlinecol(g_lastkwpos), g_lastkw)
2293    end,
2294
2295    addlog = function()
2296        return format("print(%q..':%d: addlog')", g_filename, getlinecol(g_lastkwpos))
2297    end,
2298
2299    addlogvar = function(val)
2300        return format("printf(%q..':%d: addlogvar %%s', %s)", g_filename, getlinecol(g_lastkwpos), val)
2301    end,
2302
2303    debug = function(val)
2304        return format("print(%q..':%d: debug %d')", g_filename, getlinecol(g_lastkwpos), val)
2305    end,
2306
2307    getzrange = function(...)
2308        local v = {...}
2309        assert(#v == 10)  -- 4R 4W 2R
2310        return format("%s,%s,%s,%s=_con._getzrange(%s,%s,%s,%s,%s,%s)",
2311                      v[5], v[6], v[7], v[8],  -- outargs
2312                      v[1], v[2], v[3], v[4], v[9], v[10])  -- inargs
2313    end,
2314
2315    hitscan = function(...)
2316        local v = {...}
2317        assert(#v == 14)  -- 7R 6W 1R
2318        local vals = {
2319            v[8], v[9], v[10], v[11], v[12], v[13],  -- outargs
2320            v[1], v[2], v[3], v[4], v[5], v[6], v[7], v[14]  -- inargs
2321        }
2322        return format("%s,%s,%s,%s,%s,%s=_con._hitscan(%s,%s,%s,%s,%s,%s,%s,%s)",
2323                     unpack(vals))
2324    end,
2325
2326    neartag = function(...)
2327        local v = {...}
2328        assert(#v == 11)  -- 5R 4W 2R
2329        local vals = {
2330            v[6], v[7], v[8], v[9],  -- outargs
2331            v[1], v[2], v[3], v[4], v[5], v[10], v[11]  -- inargs
2332        }
2333        return format("%s,%s,%s,%s=_con._neartag(%s,%s,%s,%s,%s,%s,%s)",
2334                      unpack(vals))
2335    end,
2336
2337    clipmove = function(noslidep, ...)
2338        local v = {...}
2339        assert(#v == 11)  -- 3W 1R 1W 6R
2340        local vals = {
2341            v[1], v[2], v[3], v[5],  -- outargs
2342            v[2], v[3], v[4], v[5], v[6], v[7], v[8], v[9], v[10], v[11],  -- inargs
2343            noslidep
2344        }
2345        return format("%s,%s,%s,%s=_con._clipmovex("..n_s_fmt(11)..")",
2346                     unpack(vals))
2347    end,
2348
2349    palfrom = function(...)
2350        local v = {...}
2351        return format(PLS":_palfrom(%d,%d,%d,%d)",
2352                      v[1] or 0, v[2] or 0, v[3] or 0, v[4] or 0)
2353    end,
2354
2355    qsprintf = function(qdst, qsrc, ...)
2356        local codes = {...}
2357        return format("_con._qsprintf(%s,%s%s%s)", qdst, qsrc,
2358                      #codes>0 and "," or "", table.concat(codes, ','))
2359    end,
2360
2361    move = function(mv, ...)
2362        local flags = {...}
2363        return format(ACS":set_move(%s,%d)", mv, (flags[1] and bit.bor(...)) or 0)
2364    end,
2365
2366    rotatesprite = function(...)
2367        return format("_con._rotspr(%s,%s,%s,%s,%s,%s,%s,%s,0,%s,%s,%s,%s)", ...)
2368    end,
2369
2370    rotatesprite16 = function(...)  -- (orientation|ROTATESPRITE_FULL16)
2371        return format("_con._rotspr(%s,%s,%s,%s,%s,%s,%s,_bor(%s,2048),0,%s,%s,%s,%s)", ...)
2372    end,
2373
2374    rotatespritea = function(...)
2375        return format("_con._rotspr(%s,%s,%s,%s,%s,%s,%s,%s,%s,%s,%s,%s,%s)", ...)
2376    end,
2377
2378    -- <fmt>: format string, number of %s's must match number of varargs
2379    arraycmd = function(fmt, dstargi, ...)
2380        local args = {...}
2381        if (issysgar(args[dstargi])) then
2382            errprintf("%s: system gamearray not supported", g_lastkw)
2383        end
2384        return format(fmt, ...)
2385    end,
2386
2387    -- readgamevar or savegamevar
2388    RSgamevar = function(identifier, dosave)
2389        -- check identifier for sanity
2390        if (not identifier:match("^[A-Za-z][A-Za-z0-9_%-]*$")) then
2391            errprintf("%s: bad identifier `%s' for config file persistence",
2392                      g_lastkw, identifier)
2393            return "_BADRSGV()"
2394        end
2395
2396        local gv = g_gamevar[identifier]
2397        if (gv == nil) then
2398            return lookup.error_not_gamevar(identifier)
2399        end
2400
2401        -- For per-actor or per-player gamevars, the value at the current actor or
2402        -- player index gets saved / loaded.
2403        local gvkind = bit.band(gv.flags, GVFLAG.PERX_MASK)
2404        local index = (gvkind==GVFLAG.PERACTOR) and "_aci" or
2405            (gvkind==GVFLAG.PERPLAYER) and "_pli" or nil
2406
2407        -- NOTE: more strict than C-CON: we require the gamevar being writable
2408        -- even if we're saving it.
2409        local code = lookup.gamevar(identifier, index, true)
2410
2411        gv.used = bit.bor(gv.used, not dosave and 2 or 1)
2412
2413        if (dosave) then
2414            return format("_con._savegamevar(%q,%s)", identifier, code)
2415        else
2416            return format("%s=_con._readgamevar(%q,%s)", code, identifier, code)
2417        end
2418    end,
2419
2420    state = function(statename)
2421        if (g_funcname[statename]==nil) then
2422            local warn = not g_cgopt["error-nostate"]
2423            local xprintf = warn and warnprintf or errprintf
2424
2425            xprintf("state `%s' not found.", statename)
2426            return warn and "" or "_NULLSTATE()"
2427        end
2428        return format("%s(_aci,_pli,_dist)", g_funcname[statename])
2429    end,
2430
2431    addweapon = format("if (%s) then _con.longjmp() end", PLS":addweapon(%1,%2)"),
2432
2433    -- Sound commands
2434    sound = "_con._sound(_aci,%1)",
2435    globalsound = "_con._globalsound(_pli,%1)",
2436    stopsound = "_con._stopsound(_aci,%1)",
2437    soundonce = "_con._soundonce(_aci,%1)",
2438}
2439
2440local userdef_common_pat = (arraypat_maybe_empty + sp1)/{}
2441    * lpeg.Cc(0) * lpeg.Ct(patt.singlemember) * sp1
2442
2443-- NOTE about prefixes: most is handled by all_alt_pattern(), however commands
2444-- that have no arguments and that are prefixes of other commands MUST be
2445-- suffixed with a "* #sp1" pattern.
2446
2447local Cinner = {
2448    -- these can appear anywhere in the script
2449    ["break"] = cmd()
2450        / function()
2451              return g_isWhile[#g_isWhile]
2452                  and format("goto l%d", #g_isWhile)
2453                  or "do return end"
2454          end,
2455    ["return"] = cmd()  -- NLCF
2456        / "_con.longjmp()",
2457
2458    state = cmd(I)
2459        / handle.state,
2460
2461    --- 1. get*, set*
2462    getsector = GetStructCmd(Access.sector),
2463    getwall = GetStructCmd(Access.wall),
2464    getactor = GetStructCmd(Access.xsprite),
2465    getplayer = GetStructCmd(Access.player),
2466
2467    getinput = GetStructCmd(Access.input),
2468    getprojectile = GetStructCmd(Access.projectile),
2469    getthisprojectile = GetStructCmd(Access.thisprojectile),
2470    gettspr = GetStructCmd(Access.tspr),
2471    -- NOTE: {get,set}userdef is the only struct that can be accessed without
2472    -- an "array part", e.g.  H266MOD has "setuserdef .weaponswitch 0" (space
2473    -- between keyword and "." is mandatory).
2474    -- NOTE2: userdef has at least three members with a second parameter:
2475    -- user_name, ridecule, savegame. Then there's wchoice. Given that they're
2476    -- arrays, I highly doubt that they worked (much less were safe) in CON.
2477    -- We disallow them, recent EDuke32 versions didn't expose them either.
2478    getuserdef = GetStructCmd(Access.userdef, userdef_common_pat * tok.wvar),
2479
2480    getplayervar = GetOrSetPerxvarCmd(false, false),  -- THISACTOR
2481    getactorvar = GetOrSetPerxvarCmd(false, true),
2482
2483    setsector = SetStructCmd(Access.sector),
2484    setwall = SetStructCmd(Access.wall),
2485    setactor = SetStructCmd(Access.xsprite),
2486    setplayer = SetStructCmd(Access.player),
2487
2488    setinput = SetStructCmd(Access.input),
2489    setprojectile = SetStructCmd(Access.projectile),
2490    setthisprojectile = SetStructCmd(Access.thisprojectile),
2491    settspr = SetStructCmd(Access.tspr),
2492    setuserdef = SetStructCmd(Access.userdef, userdef_common_pat * tok.rvar),
2493
2494    setplayervar = GetOrSetPerxvarCmd(true, false),  -- THISACTOR
2495    setactorvar = GetOrSetPerxvarCmd(true, true),
2496
2497    setvarvar = Op.varvar / "%1=%2",
2498    addvarvar = Op.varvarf "+",
2499    -- NOTE the space after the minus sign so that e.g. "subvar x -1" won't get
2500    -- translated to "x=x--1" (-- being the Lua line comment start).
2501    subvarvar = Op.varvarf "- ",
2502    mulvarvar = Op.varvarf("*", "_mulTR", "_mulWR"),
2503    divvarvar = Op.varvarf "_div",
2504    modvarvar = Op.varvarf "_mod",
2505    andvarvar = Op.varvarf "_band",
2506    orvarvar = Op.varvarf "_bor",
2507    xorvarvar = Op.varvarf "_bxor",
2508    randvarvar = Op.varvar / "%1=_con._rand(%2)",
2509
2510    setvar = Op.var / "%1=%2",
2511    addvar = Op.varf "+",
2512    subvar = Op.varf "- ",
2513    mulvar = Op.varf("*", "_mulTR", "_mulWR"),
2514    divvar = Op.varf "_div",
2515    modvar = Op.varf "_mod",
2516    andvar = Op.varf "_band",
2517    orvar = Op.varf "_bor",
2518    xorvar = Op.varf "_bxor",
2519    randvar = Op.var / "%1=_con._rand(%2)",
2520    shiftvarl = Op.varf "_lsh",
2521    shiftvarr = Op.varf "_arsh",
2522
2523    --- 2. Math operations
2524    sqrt = cmd(R,W)
2525        / "%2=_gv.ksqrt(%1)",
2526    calchypotenuse = cmd(W,R,R)
2527        / "%1=_con._hypot(%2,%3)",
2528    sin = cmd(W,R)
2529        / "%1=_xmath.ksin(%2)",
2530    cos = cmd(W,R)
2531        / "%1=_xmath.kcos(%2)",
2532    mulscale = cmd(W,R,R,R)
2533        / "%1=_gv.Mulscale(%2,%3,%4)",
2534    getangle = cmd(W,R,R)
2535        / "%1=_gv.getangle(%2,%3)",
2536    getincangle = cmd(W,R,R)
2537        / "%1=_con._angdiff(%2,%3)",
2538
2539    --- 3. Actors
2540    action = cmd(AC)
2541        / ACS":set_action(%1)",
2542    ai = cmd(AI)
2543        / ACS":set_ai(%1)",
2544    move = sp1 * tok.move * (sp1 * tok.define)^0
2545        / handle.move,
2546
2547    cactor = cmd(D)
2548        / SPS":set_picnum(%1)",
2549    count = cmd(D)
2550        / ACS":set_count(%1)",
2551    cstator = cmd(D)
2552        / (SPS".cstat=_bor(%1,"..SPS".cstat)"),
2553    cstat = cmd(D)
2554        / SPS".cstat=%1",
2555    clipdist = cmd(D)
2556        / SPS".clipdist=%1",
2557    shadeto = cmd(D) /  -- PRE13
2558        "",
2559    sizeto = cmd(D,D)
2560        / "_con._sizeto(_aci,%1,%2)",  -- TODO: see control.lua:_sizeto
2561    sizeat = cmd(D,D)
2562        / (SPS".xrepeat,"..SPS".yrepeat=%1,%2"),
2563    strength = cmd(D)
2564        / SPS".extra=%1",
2565    addstrength = cmd(D)
2566        / (SPS".extra="..SPS".extra+%1"),
2567    spritepal = cmd(D)
2568        / SPS".pal=%1",
2569
2570    hitradius = cmd(D,D,D,D,D)
2571        / "_con._A_RadiusDamage(_aci,%1,%2,%3,%4,%5)",
2572    hitradiusvar = cmd(R,R,R,R,R)
2573        / "_con._A_RadiusDamage(_aci,%1,%2,%3,%4,%5)",
2574
2575    -- some commands taking read vars
2576    operaterespawns = cmd(R)
2577        / "_con._G_OperateRespawns(%1)",
2578    operatemasterswitches = cmd(R)
2579        / "_con._G_OperateMasterSwitches(%1)",
2580    checkactivatormotion = cmd(R)
2581        / "_gv.RETURN=_con._checkactivatormotion(%1)",
2582    time = cmd(R)  -- no-op
2583        / "",
2584    inittimer = cmd(R)
2585        / "_con._inittimer(%1)",
2586    lockplayer = cmd(R)
2587        / PLS".transporter_hold=%1",
2588    quake = cmd(R)
2589        / "_gv.doQuake(%1,81)",  -- TODO: dynsound (EARTHQUAKE)
2590    jump = cmd(R)
2591        / handle.NYI,  -- will never be
2592    cmenu = cmd(R)
2593        / "_gv._changeMenu(%1)",
2594    checkavailweapon = cmd(R)  -- THISACTOR
2595        / function(pli)
2596              return format("_con._checkavailweapon(%s)", thisactor_to_pli(pli))
2597          end,
2598    checkavailinven = cmd(R)  -- THISACTOR
2599        / function(pli)
2600              return format("_con._selectnextinv(player[%s])", thisactor_to_pli(pli))
2601          end,
2602    guniqhudid = cmd(R)
2603        / "_gv._set_guniqhudid(%1)",
2604    echo = cmd(R)
2605        / "_con._echo(%1)",
2606    activatecheat = cmd(R)
2607        / handle.NYI,
2608    setgamepalette = cmd(R)
2609        / "_con._setgamepalette(_pli,%1)",
2610
2611    -- Sound commands
2612    sound = cmd(D)
2613        / handle.sound,
2614    soundvar = cmd(R)
2615        / handle.sound,
2616    globalsound = cmd(D)
2617        / handle.globalsound,
2618    globalsoundvar = cmd(R)
2619        / handle.globalsound,
2620    stopsound = cmd(D)
2621        / handle.stopsound,
2622    stopsoundvar = cmd(R)
2623        / handle.stopsound,
2624    soundonce = cmd(D)
2625        / handle.soundonce,
2626    soundoncevar = cmd(R)
2627        / handle.soundonce,
2628    stopactorsound = cmd(R,R)
2629        / "_con._stopactorsound(%1,%2)",
2630    stopallsounds = cmd()
2631        / "_con._stopallsounds()",
2632    screensound = cmd(R)
2633        / "_con._screensound(%1)",
2634    mikesnd = cmd()
2635        / format("_con._soundonce(_aci,%s)", SPS".yvel"),
2636    setactorsoundpitch = cmd(R,R,R)
2637        / "_con._setactorsoundpitch(%1,%2,%3)",
2638
2639    -- some commands taking defines
2640    addammo = cmd(D,D)  -- NLCF
2641        / format("if (%s) then _con.longjmp() end", PLS":addammo(%1,%2)"),
2642    addweapon = cmd(D,D)  -- NLCF
2643        / handle.addweapon,
2644    debris = cmd(D,D)
2645        / "_con._debris(_aci, %1, %2)",
2646    addinventory = cmd(D,D)
2647        / format("_con._addinventory(%s,%%1,%%2,_aci)", PLS""),
2648    guts = cmd(D,D)
2649        / "_con._A_DoGuts(_aci,%1,%2)",
2650
2651    spawn = cmd(D)
2652        / "_con.spawn(%1,_aci)",
2653    espawn = cmd(D)
2654        / "_gv.RETURN=_con.spawn(%1,_aci)",
2655    espawnvar = cmd(R)
2656        / "_gv.RETURN=_con.spawn(%1,_aci)",
2657    qspawn = cmd(D)
2658        / "_con.spawn(%1,_aci,true)",
2659    qspawnvar = cmd(R)
2660        / "_con.spawn(%1,_aci,true)",
2661    eqspawn = cmd(D)
2662        / "_gv.RETURN=_con.spawn(%1,_aci,true)",
2663    eqspawnvar = cmd(R)
2664        / "_gv.RETURN=_con.spawn(%1,_aci,true)",
2665
2666    angoff = cmd(D)
2667        / "spriteext[_aci].angoff=%1",
2668    angoffvar = cmd(R)
2669        / "spriteext[_aci].angoff=%1",
2670
2671    -- cont'd
2672    addkills = cmd(D)
2673        / (PLS".actors_killed="..PLS".actors_killed+%1;"..ACS".stayputsect=-1"),
2674    addphealth = cmd(D)
2675        / format("_con._addphealth(%s,_aci,%%1)", PLS""),
2676    debug = cmd(D)
2677        / handle.debug,
2678    endofgame = cmd(D)
2679        / "_con._endofgame(_pli,%1)",
2680    endoflevel = cmd(D)  -- PRE13
2681        / "_con._endofgame(_pli,%1)",
2682    lotsofglass = cmd(D)
2683        / "_con._A_SpawnGlass(_aci,%1)",
2684    mail = cmd(D)
2685        / "_con._spawnmany(_aci,'MAIL',%1)",
2686    money = cmd(D)
2687        / "_con._spawnmany(_aci,'MONEY',%1)",
2688    paper = cmd(D)
2689        / "_con._spawnmany(_aci,'PAPER',%1)",
2690    sleeptime = cmd(D)
2691        / ACS".timetosleep=%1",
2692
2693    eshoot = cmd(D)
2694        / "_gv.RETURN=_con.shoot(%1,_aci)",
2695    eshootvar = cmd(R)
2696        / "_gv.RETURN=_con.shoot(%1,_aci)",
2697    ezshoot = cmd(R,D)
2698        / "_gv.RETURN=_con.shoot(%2,_aci,%1)",
2699    ezshootvar = cmd(R,R)
2700        / "_gv.RETURN=_con.shoot(%2,_aci,%1)",
2701    shoot = cmd(D)
2702        / "_con.shoot(%1,_aci)",
2703    shootvar = cmd(R)
2704        / "_con.shoot(%1,_aci)",
2705    zshoot = cmd(R,D)
2706        / "_con.shoot(%2,_aci,%1)",
2707    zshootvar = cmd(R,R)
2708        / "_con.shoot(%2,_aci,%1)",
2709
2710    fall = cmd()
2711        / "actor.fall(_aci)",
2712    flash = cmd()
2713        / format("_con._flash(%s,%s)", SPS"", PLS""),
2714    getlastpal = cmd()
2715        / "_con._getlastpal(_aci)",
2716    insertspriteq = cmd()
2717        / "_con._addtodelqueue(_aci)",
2718    killit = cmd()  -- NLCF
2719        / "_con.killit()",
2720    nullop = cmd()
2721        / "",  -- NOTE: really generate no code
2722    pkick = cmd()
2723        / format("_con._pkick(%s,%s)", PLS"", ACS""),
2724    pstomp = cmd()
2725        / PLS":stomp(_aci)",
2726    resetactioncount = cmd()
2727        / ACS":reset_acount()",
2728    resetcount = cmd()
2729        / ACS":set_count(0)",
2730    resetplayer = cmd() * #sp1  -- NLCF
2731        / "if (_con._VM_ResetPlayer2(_pli,0)) then _con.longjmp() end",
2732    resetplayerflags = cmd(R)  -- NLCF
2733        / "if (_con._VM_ResetPlayer2(_pli,%1)) then _con.longjmp() end",
2734    respawnhitag = cmd()
2735        / format("_con._respawnhitag(%s)", SPS""),
2736    tip = cmd()
2737        / PLS".tipincs=26",
2738    tossweapon = cmd()
2739        / "_con._tossweapon(_pli)",
2740    wackplayer = cmd()
2741        / PLS":whack()",
2742
2743    -- player/sprite searching
2744    findplayer = cmd(W)
2745        / "_gv.RETURN,%1=_con._findplayer(_pli,_aci)",  -- player index, distance
2746    findotherplayer = cmd(W)
2747        / "_gv.RETURN,%1=0,0x7fffffff",  -- TODO_MP
2748    findnearspritezvar = cmd(D,R,R,W)
2749        / "%4=_con._findnear(_aci,true,'z',%1,%2,%3)",
2750    findnearspritez = cmd(D,D,D,W)
2751        / "%4=_con._findnear(_aci,true,'z',%1,%2,%3)",
2752    findnearsprite3dvar = cmd(D,R,W)
2753        / "%3=_con._findnear(_aci,true,'d3',%1,%2)",
2754    findnearsprite3d = cmd(D,D,W)
2755        / "%3=_con._findnear(_aci,true,'d3',%1,%2)",
2756    findnearspritevar = cmd(D,R,W)
2757        / "%3=_con._findnear(_aci,true,'d2',%1,%2)",
2758    findnearsprite = cmd(D,D,W)
2759        / "%3=_con._findnear(_aci,true,'d2',%1,%2)",
2760    findnearactorzvar = cmd(D,R,R,W)
2761        / "%4=_con._findnear(_aci,false,'z',%1,%2,%3)",
2762    findnearactorz = cmd(D,D,D,W)
2763        / "%4=_con._findnear(_aci,false,'z',%1,%2,%3)",
2764    findnearactor3dvar = cmd(D,R,W)
2765        / "%3=_con._findnear(_aci,false,'d3',%1,%2)",
2766    findnearactor3d = cmd(D,D,W)
2767        / "%3=_con._findnear(_aci,false,'d3',%1,%2)",
2768    findnearactorvar = cmd(D,R,W)
2769        / "%3=_con._findnear(_aci,false,'d2',%1,%2)",
2770    findnearactor = cmd(D,D,W)
2771        / "%3=_con._findnear(_aci,false,'d2',%1,%2)",
2772
2773    -- quotes
2774    qsprintf = sp1 * tok.rvar * sp1 * tok.rvar * (sp1 * tok.rvar)^-32
2775        / handle.qsprintf,
2776    qgetsysstr = cmd(R,R)
2777        / "_con._qgetsysstr(%1,%2,_pli)",
2778    qstrcat = cmd(R,R)
2779        / "_con._qstrcat(%1,%2)",
2780    qstrcpy = cmd(R,R)
2781        / "_con._qstrcpy(%1,%2)",
2782    qstrlen = cmd(W,R)
2783        / "%1=_con._qstrlen(%2)",
2784    qstrncat = cmd(R,R,R)
2785        / "_con._qstrcat(%1,%2,%3)",
2786    qsubstr = cmd(R,R,R,R)
2787        / "_con._qsubstr(%1,%2,%3,%4)",
2788    quote = cmd(D)
2789        / "_con._quote(_pli,%1)",
2790    userquote = cmd(R)
2791        / "_con._userquote(%1)",
2792    getkeyname = cmd(R,R,R)
2793        / "_con._getkeyname(%1,%2,%3)",
2794    getpname = cmd(R,R)  -- THISACTOR
2795        / function(qnum, pli)
2796              return format("_con._getpname(%s,%s)", qnum, thisactor_to_pli(pli))
2797          end,
2798
2799    -- array stuff
2800    copy = sp1 * tok.gamearray * arraypat * sp1 * tok.gamearray * arraypat * sp1 * tok.rvar
2801        / function(...) return handle.arraycmd("_con._gar_copy(%s,%s,%s,%s,%s)", 3, ...) end,
2802    setarray = sp1 * tok.gamearray * arraypat * sp1 * tok.rvar
2803        / function(...) return handle.arraycmd("%s[%s]=%s", 1, ...) end,
2804    resizearray = cmd(GARI,R)
2805        / function(...) return handle.arraycmd("%s:resize(%s)", 1, ...) end,
2806    getarraysize = cmd(GARI,W)
2807        / function(ar, dst)
2808              return format("%s=%s", dst, issysgar(ar) and tostring(C.MAXTILES) or ar.."._size")
2809          end,
2810    readarrayfromfile = cmd(GARI,D)
2811        / function(...)  -- false: error on no file, nil: don't.
2812              return handle.arraycmd("%s:read(%s,nil)", 1, ...)
2813          end,
2814    writearraytofile = cmd(GARI,D)
2815        / function(...)
2816              return handle.arraycmd("%s:write(%s)", 1, ...)
2817          end,
2818
2819    -- Persistence
2820    clearmapstate = cmd(R)
2821        / "_con._clearmapstate(%1)",
2822    loadmapstate = cmd()
2823        / "_con._loadmapstate()",
2824    savemapstate = cmd()
2825        / "_con._savemapstate()",
2826    savegamevar = cmd(I)
2827        / function(id) return handle.RSgamevar(id, true) end,
2828    readgamevar = cmd(I)
2829        / function(id) return handle.RSgamevar(id, false) end,
2830    savenn = cmd(D)
2831        / handle.dynNYI,
2832    save = cmd(D)
2833        / handle.dynNYI,
2834
2835    addlogvar = cmd(R)
2836        / handle.addlogvar,
2837    addlog = cmd() * #sp1
2838        / handle.addlog,
2839    addweaponvar = cmd(R,R)  -- NLCF
2840        / handle.addweapon,
2841    cansee = cmd(R,R,R,R,R,R,R,R,W)
2842        / "%9=cansee(_IV(1,%1,%2,%3),%4, _IV(2,%5,%6,%7),%8) and 1 or 0",
2843    canseespr = cmd(R,R,W)
2844        / "%3=_con._canseespr(%1,%2)",
2845    changespritesect = cmd(R,R)
2846        / "sprite.changesect(%1,%2,true)",
2847    changespritestat = cmd(R,R)
2848        / "sprite.changestat(%1,%2,true)",
2849    displayrand = cmd(W)
2850        / "%1=_con._displayrand(32767)",
2851    displayrandvar = cmd(W,D)
2852        / "%1=_con._displayrand(%2)",
2853    displayrandvarvar = cmd(W,R)
2854        / "%1=_con._displayrand(%2)",
2855    dist = cmd(W,R,R)
2856        / "%1=_xmath.dist(sprite[%2],sprite[%3])",
2857    ldist = cmd(W,R,R)
2858        / "%1=_xmath.ldist(sprite[%2],sprite[%3])",
2859    dragpoint = cmd(R,R,R)
2860        / "wall.dragto(%1,_IV(1,%2,%3,0))",
2861    rotatepoint = cmd(R,R,R,R,R,W,W)
2862        / "%6,%7=_con._rotatepoint(%1,%2,%3,%4,%5)",
2863
2864    -- collision detection etc.
2865    hitscan = cmd(R,R,R,R,R,R,R,W,W,W,W,W,W,R)  -- 7R 6W 1R
2866        / handle.hitscan,
2867    clipmove = cmd(W,W,W,R,W,R,R,R,R,R,R)  -- 3W 1R 1W 6R
2868        / function(...) return handle.clipmove(0, ...) end,
2869    clipmovenoslide = cmd(W,W,W,R,W,R,R,R,R,R,R)  -- 3W 1R 1W 6R
2870        / function(...) return handle.clipmove(1, ...) end,
2871    lineintersect = cmd(R,R,R,R,R,R,R,R,R,R,W,W,W,W)  -- 10R 4W
2872        / handle.NYI,
2873    rayintersect = cmd(R,R,R,R,R,R,R,R,R,R,W,W,W,W)  -- 10R 4W
2874        / handle.NYI,
2875    movesprite = cmd(R,R,R,R,R,W)
2876        / "%6=_con._movesprite(%1,%2,%3,%4,%5)",
2877    neartag = cmd(R,R,R,R,R,W,W,W,W,R,R)  -- 5R 4W 2R
2878        / handle.neartag,
2879    getzrange = cmd(R,R,R,R,W,W,W,W,R,R)
2880        / handle.getzrange,
2881
2882    -- screen text and numbers display
2883    qstrdim = cmd(W,W,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R)  -- 2W 16R
2884        / function(...)
2885              return format("%s,%s=_con._qstrdim("..n_s_fmt(16)..")", ...)
2886          end,
2887    screentext = cmd(R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R,R)  -- 20 R
2888        / function(...)
2889              return format("_con._screentext("..n_s_fmt(20)..")", ...)
2890          end,
2891    gametext = cmd(R,R,R,R,R,R,R,R,R,R,R)  -- 11 R
2892        / function(...)
2893              return format("_con._gametext("..n_s_fmt(11)..",65536)", ...)
2894          end,
2895    gametextz = cmd(R,R,R,R,R,R,R,R,R,R,R,R)  -- 12 R
2896        / function(...)
2897              return format("_con._gametext("..n_s_fmt(12)..")", ...)
2898          end,
2899    digitalnumber = cmd(R,R,R,R,R,R,R,R,R,R,R)  -- 11R
2900        / function(...)
2901              return format("_con._digitalnumber("..n_s_fmt(11)..",65536)", ...)
2902          end,
2903    digitalnumberz = cmd(R,R,R,R,R,R,R,R,R,R,R,R)  -- 12R
2904        / function(...)
2905              return format("_con._digitalnumber("..n_s_fmt(12)..")", ...)
2906          end,
2907    minitext = cmd(R,R,R,R,R)
2908        / "_con._minitext(%1,%2,%3,%4,%5)",
2909
2910    palfrom = (sp1 * tok.define)^-4
2911        / handle.palfrom,
2912
2913    activatebysector = cmd(R,R)
2914        / "_con._activatebysector(%1,%2)",
2915    activate = cmd(D)  -- PRE13, THISACTOR already translated to cur. player
2916        / "_con._operateactivators(%d,_pli)",
2917    operateactivators = cmd(R,R)  -- THISACTOR
2918        / function(tag, pli)
2919              return format("_con._operateactivators(%s,%s)", tag, thisactor_to_pli(pli))
2920          end,
2921    operatesectors = cmd(R,R)
2922        / "_con._operatesectors(%1,%2)",
2923    operate = cmd() * #sp1
2924        / "_con._operate(_aci)",
2925
2926    myos = cmd(R,R,R,R,R)
2927        / "_con._myos(%1,%2,65536,%3,%4,%5)",
2928    myosx = cmd(R,R,R,R,R)
2929        / "_con._myos(%1,%2,32768,%3,%4,%5)",
2930    myospal = cmd(R,R,R,R,R,R)
2931        / "_con._myos(%1,%2,65536,%3,%4,%5,%6)",
2932    myospalx = cmd(R,R,R,R,R,R)
2933        / "_con._myos(%1,%2,32768,%3,%4,%5,%6)",
2934
2935    headspritesect = cmd(W,R)
2936        / "%1=sprite._headspritesect[%2]",
2937    headspritestat = cmd(W,R)
2938        / "%1=sprite._headspritestat[%2]",
2939    nextspritesect = cmd(W,R)
2940        / "%1=sprite._nextspritesect[%2]",
2941    nextspritestat = cmd(W,R)
2942        / "%1=sprite._nextspritestat[%2]",
2943    prevspritesect = cmd(W,R)
2944        / "%1=sprite._prevspritesect[%2]",
2945    prevspritestat = cmd(W,R)
2946        / "%1=sprite._prevspritestat[%2]",
2947
2948    -- NOTE: Yup, it's also an inner command. Do this one concession to
2949    -- cleanness for backward compatibility (e.g. Sonic3D v0.3).
2950    definequote = sp1 * tok.define * newline_term_string
2951        / Cmd.definequote,
2952
2953    redefinequote = sp1 * tok.define * newline_term_string
2954        / function(qnum, qstr) return format("_con._definequote(%d,%q)", qnum, stripws(qstr)) end,
2955    rotatesprite = cmd(R,R,R,R,R,R,R,R,R,R,R,R)  -- 12R
2956        / handle.rotatesprite,
2957    rotatesprite16 = cmd(R,R,R,R,R,R,R,R,R,R,R,R)  -- 12R
2958        / handle.rotatesprite16,
2959    rotatespritea = cmd(R,R,R,R,R,R,R,R,R,R,R,R,R)  -- 13R
2960        / handle.rotatespritea,
2961    sectorofwall = cmd(W,R,R)
2962        / handle.NYI,
2963    sectclearinterpolation = cmd(R)
2964        / "_con._togglesectinterp(%1,0)",
2965    sectsetinterpolation = cmd(R)
2966        / "_con._togglesectinterp(%1,1)",
2967
2968    sectgethitag = cmd()
2969        / (CSV".HITAG=sector["..SPS".sectnum].hitag"),
2970    sectgetlotag = cmd()
2971        / (CSV".LOTAG=sector["..SPS".sectnum].lotag"),
2972    spgethitag = cmd()
2973        / (CSV".HITAG="..SPS".hitag"),
2974    spgetlotag = cmd()
2975        / (CSV".LOTAG="..SPS".lotag"),
2976    gettextureceiling = cmd()
2977        / (CSV".TEXTURE=sector["..SPS".sectnum].ceilingpicnum"),
2978    gettexturefloor = cmd()
2979        / (CSV".TEXTURE=sector["..SPS".sectnum].floorpicnum"),
2980
2981    startlevel = cmd(R,R)
2982        / "_con._startlevel(%1,%2)",
2983    starttrack = cmd(D)
2984        / "_con._starttrack(%1)",
2985    starttrackvar = cmd(R)
2986        / "_con._starttrack(%1)",
2987    startcutscene = cmd(R)
2988        / handle.NYI,
2989
2990    getmusicposition = cmd(W)
2991        / "%1=_con._getmusicposition()",
2992    setmusicposition = cmd(R)
2993        / "_con._setmusicposition(%1)",
2994
2995    setaspect = cmd(R,R)
2996        / "_con._setaspect(%1,%2)",
2997    showview = cmd(R,R,R,R,R,R,R,R,R,R)  -- 10R
2998        / function(...) return format("_con._showview("..n_s_fmt(10)..",0)", ...) end,
2999    showviewunbiased = cmd(R,R,R,R,R,R,R,R,R,R)  -- 10R
3000        / function(...) return format("_con._showview("..n_s_fmt(10)..",1)", ...) end,
3001    smaxammo = cmd(R,R)
3002        / PLS".max_ammo_amount[%1]=%2",
3003    gmaxammo = cmd(R,W)
3004        / ("%2="..PLS".max_ammo_amount[%1]"),
3005    spriteflags = cmd(R)  -- also see outer
3006        / ACS".flags=%1",
3007    ssp = cmd(R,R)
3008        / "_ssp(%1,%2)",
3009    setsprite = cmd(R,R,R,R)
3010        / "_setsprite(%1,_IV(1,%2,%3,%4))",
3011    updatesector = cmd(R,R,W)
3012        / format("%%3=updatesector(_IV(1,%%1,%%2,0),%s)", SPS".sectnum"),
3013    updatesectorz = cmd(R,R,R,W)
3014        / format("%%4=updatesectorz(_IV(1,%%1,%%2,%%3),%s)", SPS".sectnum"),
3015
3016    getactorangle = cmd(W)
3017        / ("%1="..SPS".ang"),
3018    setactorangle = cmd(R)
3019        / SPS".ang=_band(%1,2047)",
3020    getplayerangle = cmd(W)
3021        / ("%1="..PLS".ang"),
3022    setplayerangle = cmd(R)
3023        / PLS".ang=_band(%1,2047)",
3024    getangletotarget = cmd(W)
3025        / "%1=_con._angtotarget(_aci)",
3026
3027    getceilzofslope = cmd(R,R,R,W)
3028        / "%4=sector[%1]:ceilingzat(_IV(1,%2,%3,0))",
3029    getflorzofslope = cmd(R,R,R,W)
3030        / "%4=sector[%1]:floorzat(_IV(1,%2,%3,0))",
3031    getcurraddress = cmd(W)
3032        / handle.NYI,  -- will never be
3033    getticks = cmd(W)
3034        / "%1=_gv.getticks()",
3035    gettimedate = cmd(W,W,W,W,W,W,W,W)
3036        / "%1,%2,%3,%4,%5,%6,%7,%8=_con._gettimedate()",
3037}
3038
3039local Cif = {
3040    ifai = cmd(AI)
3041        / ACS":has_ai(%1)",
3042    ifaction = cmd(AC)
3043        / ACS":has_action(%1)",
3044    ifmove = cmd(MV)
3045        / ACS":has_move(%1)",
3046
3047    ifrnd = cmd(D)
3048        / "_con.rnd(%1)",
3049    ifpdistl = cmd(D)  -- DEFER
3050        / function(val) return { "_dist<"..val, nil, "_con._sleepcheck(_aci,_dist)" } end,
3051    ifpdistg = cmd(D)  -- DEFER
3052        / function(val) return { "_dist>"..val, nil, "_con._sleepcheck(_aci,_dist)" } end,
3053    ifactioncount = cmd(D)
3054        / ACS":get_acount()>=%1",
3055    ifcount = cmd(D)
3056        / ACS":get_count()>=%1",
3057    ifactor = cmd(D)
3058        / SPS".picnum==%1",
3059    ifstrength = cmd(D)
3060        / SPS".extra<=%1",
3061    ifspawnedby = cmd(D)
3062        / ACS".picnum==%1",
3063    ifwasweapon = cmd(D)
3064        / ACS".picnum==%1",
3065    ifgapzl = cmd(D)  -- factor into a con.* function?
3066        / format("_arsh(%s-%s,8)<%%1", ACS".floorz", ACS".ceilingz"),
3067    iffloordistl = cmd(D)
3068        / format("(%s-%s)<=256*%%1", ACS".floorz", SPS".z"),
3069    ifceilingdistl = cmd(D)
3070        / format("(%s-%s)<=256*%%1", SPS".z", ACS".ceilingz"),
3071    ifphealthl = cmd(D)
3072        / format("sprite[%s].extra<%%1", PLS".i"),
3073    ifplayersl = cmd(D)  -- PRE13
3074        / "1<%1",  -- TODO_MP
3075    ifspritepal = cmd(D)
3076        / SPS".pal==%1",
3077    ifgotweaponce = cmd(D)
3078        / "false",  -- TODO_MP
3079    ifangdiffl = cmd(D)
3080        / format("_con._angdiffabs(%s,%s)<=%%1", PLS".ang", SPS".ang"),
3081    ifsound = cmd(D)
3082        / "_con._soundplaying(_aci,%1)",
3083    ifpinventory = cmd(D,D)
3084        / format("_con._checkpinventory(%s,%%1,%%2,_aci)", PLS""),
3085
3086    ifvarl = cmd(R,D)
3087        / "%1<%2",
3088    ifvarg = cmd(R,D)
3089        / "%1>%2",
3090    ifvare = cmd(R,D)
3091        / "%1==%2",
3092    ifvarn = cmd(R,D)
3093        / "%1~=%2",
3094    ifvarand = cmd(R,D)
3095        / "_band(%1,%2)~=0",
3096    ifvaror = cmd(R,D)
3097        / "_bor(%1,%2)~=0",
3098    ifvarxor = cmd(R,D)
3099        / "_bxor(%1,%2)~=0",
3100    ifvareither = cmd(R,D)
3101        / "%1~=0 or %2~=0",
3102
3103    ifvarvarl = cmd(R,R)
3104        / "%1<%2",
3105    ifvarvarg = cmd(R,R)
3106        / "%1>%2",
3107    ifvarvare = cmd(R,R)
3108        / "%1==%2",
3109    ifvarvarn = cmd(R,R)
3110        / "%1~=%2",
3111    ifvarvarand = cmd(R,R)
3112        / "_band(%1,%2)~=0",
3113    ifvarvaror = cmd(R,R)
3114        / "_bor(%1,%2)~=0",
3115    ifvarvarxor = cmd(R,R)
3116        / "_bxor(%1,%2)~=0",
3117    ifvarvareither = cmd(R,R)
3118        / "%1~=0 or %2~=0",
3119
3120    ifactorsound = cmd(R,R)
3121        / "_con._soundplaying(%1,%2)",
3122    ifcutscene = cmd(R)
3123        / function(cs)
3124            handle.NYI()
3125            return "false"
3126          end,
3127
3128    ifp = (sp1 * tok.define)^1
3129        / function(...) return format("_con._ifp(%d,_pli,_aci)", bit.bor(...)) end,
3130    ifsquished = cmd()
3131        / "_con._squished(_aci,_pli)",
3132    ifserver = cmd()
3133        / "false",  -- TODO_MP
3134    ifrespawn = cmd()
3135        / format("_con._checkrespawn(%s)", SPS""),
3136    ifoutside = cmd()
3137        / format("_band(sector[%s].ceilingstat,1)~=0", SPS".sectnum"),
3138    ifonwater = cmd()
3139        / format("sector[%s].lotag==1 and _math.abs(%s-sector[%s].floorz)<32*256",
3140                 SPS".sectnum", SPS".z", SPS".sectnum"),
3141    ifnotmoving = cmd()
3142        / "_band(actor[_aci]._movflag,49152)>16384",
3143    ifnosounds = cmd()
3144        / "not _con._ianysound(_aci)",
3145    ifmultiplayer = cmd()
3146        / "false",  -- TODO_MP
3147    ifinwater = cmd()
3148        / format("sector[%s].lotag==2", SPS".sectnum"),
3149    ifinspace = cmd()
3150        / format("_con._checkspace(%s,false)", SPS".sectnum"),
3151    ifinouterspace = cmd()
3152        / format("_con._checkspace(%s,true)", SPS".sectnum"),
3153    ifhitweapon = cmd()
3154        / "_con._A_IncurDamage(_aci)>=0",
3155    ifhitspace = cmd()
3156        / "player.holdskey(_pli,'OPEN')",
3157    ifdead = cmd()
3158        / SPS".extra<=0",
3159    ifclient = cmd()
3160        / "false",  -- TODO_MP
3161    ifcanshoottarget = cmd()
3162        / "_con._canshoottarget(_dist,_aci)",
3163    ifcanseetarget = cmd()  -- DEFER -- XXX: 1536 is SLEEPTIME
3164        / function()
3165              return { format("_con._canseetarget(%s,%s)", SPS"", PLS""), ACS".timetosleep=1536" }
3166          end,
3167    ifcansee = cmd() * #sp1
3168        / format("_con._cansee(_aci,%s)", PLS""),
3169    ifbulletnear = cmd()
3170        / "_con._bulletnear(_aci)",
3171    ifawayfromwall = cmd()
3172        / format("_con._awayfromwall(%s,108)", SPS""),
3173    ifactornotstayput = cmd()
3174        / ACS".stayputsect==-1",
3175}
3176
3177
3178----==== Tracing and reporting ====----
3179
3180-- g_newlineidxs will contain the 1-based file offsets to "\n" characters
3181local g_newlineidxs = {}
3182
3183-- Returns index into the sorted table tab such that
3184--   tab[index] <= searchelt < tab[index+1].
3185-- Preconditions:
3186--  tab[i] < tab[i+1] for 0 <= i < #tab
3187--  tab[0] <= searchelt < tab[#tab]
3188-- If #tab is less than 2, returns 0. This plays nicely with newline index
3189-- tables like { [0]=0, [1]=len+1 }, e.g. if the file doesn't contain any.
3190local function bsearch(tab, searchelt)
3191--    printf("bsearch(tab, %d)", searchelt)
3192    local l, r = 0, #tab
3193    local i
3194
3195    if (r < 2) then
3196        return 0
3197    end
3198
3199    while (l ~= r) do
3200        i = l + math.ceil((r-l)/2)  -- l < i <= r
3201        assert(l < i and i <= r)
3202        local elt = tab[i]
3203--        printf("l=%d tab[%d]=%d r=%d", l, i, elt, r)
3204
3205        if (searchelt == elt) then
3206            return i
3207        end
3208
3209        if (searchelt < elt) then
3210            r = i-1
3211        else  -- (searchelt > elt)
3212            l = i
3213        end
3214    end
3215
3216--    printf("return tab[%d]=%d", l, tab[l])
3217    return l
3218end
3219
3220function getlinecol(pos)  -- local
3221    assert(type(pos)=="number")
3222    local line = bsearch(g_newlineidxs, pos)
3223    assert(line and g_newlineidxs[line]<=pos and pos<g_newlineidxs[line+1])
3224    local col = pos-g_newlineidxs[line]
3225    if (col == 0) then
3226        -- XXX: we probably have an off-by-one error somewhere and it would
3227        -- need to be fixed instead of doing these ugly workarounds.
3228        line = line-1
3229        col = pos-g_newlineidxs[line]
3230    end
3231    assert(col >= 1)
3232    return line+1, col-1
3233end
3234
3235-- A generic trace function, prints a position together with the match content.
3236-- The 'doit' parameter can be used to temporarily enable/disable a particular
3237-- tracing function.
3238local function TraceFunc(pat, label, doit)
3239    assert(doit ~= nil)
3240    pat = Pat(pat)
3241
3242    if (doit) then
3243        local function tfunc(subj, pos, a)
3244            printf("%s:%s: %s", linecolstr(pos), label, a)
3245            return true
3246        end
3247        pat = lpeg.Cmt(pat, tfunc)
3248    elseif (label=="kw") then  -- HACK
3249        local function tfunc(subj, pos, a)
3250            g_lastkwpos = pos
3251            g_lastkw = a
3252            return true
3253        end
3254        -- XXX: is there a better way?
3255        pat = lpeg.Cmt(pat, tfunc)
3256    end
3257
3258    return pat
3259end
3260
3261local function BadIdent(pat)
3262    local function tfunc(subj, pos, a)
3263        if (g_warn["bad-identifier"] and not g_badids[a]) then
3264            warnprintf("bad identifier: %s", a)
3265            g_badids[a] = true
3266        end
3267        return true
3268    end
3269    return lpeg.Cmt(Pat(pat), tfunc)
3270end
3271
3272-- These are tracers for specific patterns which can be disabled
3273-- if desired.
3274local function Keyw(kwname) return TraceFunc(kwname, "kw", false) end
3275--local function NotKeyw(text) return TraceFunc(text, "!kw", false) end
3276--local function Ident(idname) return TraceFunc(idname, "id", false) end
3277local function Stmt(cmdpat) return TraceFunc(cmdpat, "st", false) end
3278
3279--local function Temp(kwname) return TraceFunc(kwname, "temp", true) end
3280--Cinner["myosx"] = Temp(Cinner["myosx"])
3281
3282----==== Translator continued ====----
3283local function attachlinenum(capts, pos)
3284    capts[1] = capts[1].."--"..getlinecol(pos)
3285    return capts[1]
3286end
3287
3288local function after_inner_cmd_Cmt(subj, pos, ...)
3289    if (g_numerrors == inf) then
3290        return nil
3291    end
3292
3293    local capts = {...}
3294    assert(type(capts[1])=="string" and capts[2]==nil)
3295    return true, attachlinenum(capts, pos)
3296end
3297
3298local function after_if_cmd_Cmt(subj, pos, ...)
3299    if (g_numerrors == inf) then
3300        return nil
3301    end
3302
3303    local capts = {...}
3304    assert(capts[1] ~= nil)
3305    assert(#capts <= 3)
3306
3307    for i=#capts,1, -1 do
3308        assert(type(capts[i])=="string" or type(capts[i])=="table")
3309    end
3310
3311    -- IF_LINE_NUMBERING
3312    local firstistab = (type(capts[1])=="table")
3313    attachlinenum(firstistab and capts[1] or capts, pos)
3314
3315    return true, unpack(capts)
3316end
3317
3318local function after_cmd_Cmt(subj, pos, ...)
3319    if (g_numerrors == inf) then
3320--        print("Aborting parsing...")
3321        return nil  -- make the match fail, bail out of parsing
3322    end
3323
3324    return true  -- don't return any captures
3325end
3326
3327-- Attach the command names at the front!
3328local function attachnames(kwtab, matchtimefunc)
3329    for cmdname,cmdpat in pairs(kwtab) do
3330        -- The match-time function capture at the end is so that every command
3331        -- acts as a barrier to captures to delay (but not fully prevent) stack
3332        -- overflow (and to make lpeg.match return a subject position at the
3333        -- end)
3334        local newpat = Keyw(cmdname) * cmdpat
3335        if (cmdname~="break") then
3336            kwtab[cmdname] = lpeg.Cmt(newpat, matchtimefunc)
3337        else
3338            -- Must not attack a Cmt to "break" because it would break the
3339            -- while/switch sequencing.
3340            kwtab[cmdname] = newpat
3341        end
3342    end
3343end
3344
3345attachnames(Couter, after_cmd_Cmt)
3346attachnames(Cinner, after_inner_cmd_Cmt)
3347attachnames(Cif, after_if_cmd_Cmt)
3348
3349
3350-- Takes one or more tables and +'s all its patterns together in reverse
3351-- lexicographical order.
3352-- Each such PATTAB must be a table that maps command names to their patterns.
3353local function all_alt_pattern(...)
3354    local cmds = {}
3355
3356    local args = {...}
3357    assert(#args <= 2)
3358
3359    for argi=1,#args do
3360        local pattab = args[argi]
3361
3362        -- pairs() iterates in undefined order, so we first fill in the names...
3363        for cmdname,_ in pairs(pattab) do
3364            cmds[#cmds+1] = cmdname
3365        end
3366    end
3367
3368    -- ...and then sort them in ascending lexicographical order
3369    table.sort(cmds)
3370
3371    local pat = Pat(false)
3372
3373    for i=1,#cmds do
3374        local ourpat = args[1][cmds[i]] or args[2][cmds[i]]
3375        -- shorter commands go at the end!
3376        pat = pat + ourpat
3377    end
3378
3379    return pat
3380end
3381
3382-- actor ORGANTIC is greeting!
3383function on.lonely_else(pos)
3384    pwarnprintf(pos, "found `else' with no `if'")
3385end
3386
3387local con_inner_command = all_alt_pattern(Cinner)
3388local con_if_begs = all_alt_pattern(Cif)
3389
3390local lone_else = (POS() * "else" * sp1)/on.lonely_else
3391
3392local stmt_list = Var("stmt_list")
3393-- possibly empty statement list:
3394local stmt_list_or_eps = lpeg.Ct((stmt_list * sp1)^-1)
3395local stmt_list_nosp_or_eps = lpeg.Ct((stmt_list * (sp1 * stmt_list)^0)^-1)
3396
3397-- Reused LPeg patterns
3398local common = {}
3399
3400-- common to actor and useractor: <name/tilenum> [<strength> [<action> [<move> [<flags>... ]]]]
3401common.actor_end = sp1 * lpeg.Ct(tok.actordefine *
3402    (sp1 * tok.define *
3403     (sp1 * tok.action *
3404      (sp1 * tok.move *
3405       (sp1 * tok.define)^0
3406      )^-1
3407     )^-1
3408    )^-1)
3409* sp1 * stmt_list_or_eps * "enda"
3410
3411common.block_begin = lpeg.Cc(nil) / function()
3412    g_switchCode = {}
3413end
3414
3415common.block_end = lpeg.Cc(nil) / function()
3416    if (#g_switchCode > 0) then
3417        addcode(g_switchCode)
3418    end
3419    g_switchCode = nil
3420end
3421
3422--== block delimiters (no syntactic recursion) ==--
3423local Cblock = {
3424    -- actor (...)
3425    actor = POS() * lpeg.Cc(nil) * common.actor_end / on.actor_end,
3426    -- useractor <actortype> (...)
3427    useractor = POS() * sp1 * tok.define * common.actor_end / on.actor_end,
3428    -- eventloadactor <name/tilenum>
3429    eventloadactor = POS() * sp1 * tok.actordefine * sp1 * stmt_list_or_eps * "enda"
3430        / on.eventloadactor_end,
3431
3432    onevent = POS() * sp1 * tok.define * sp1 * stmt_list_or_eps * "endevent"
3433        / on.event_end,
3434    appendevent = POS() * sp1 * tok.define * sp1 * stmt_list_or_eps * "endevent"
3435        / on.appendevent_end,
3436
3437    state = POS() * sp1 * (lpeg.Cmt(tok.identifier, on.state_begin_Cmt))
3438                  * sp1 * stmt_list_or_eps * tok.state_ends
3439        / on.state_end,
3440    defstate = POS() * sp1 * (lpeg.Cmt(tok.identifier, on.state_begin_Cmt))
3441                     * sp1 * stmt_list_or_eps * tok.state_ends
3442        / on.state_end,
3443}
3444
3445for cmdname, cmdpat in pairs(Cblock) do
3446    Cblock[cmdname] = common.block_begin * cmdpat * common.block_end
3447end
3448
3449attachnames(Cblock, after_cmd_Cmt)
3450
3451
3452local t_good_identifier = Range("AZ", "az", "__") * Range("AZ", "az", "__", "09")^0
3453
3454-- CON isaltok also has chars in "{}.", but these could potentially
3455-- interfere with *CON* syntax.  The "]" is so that the number in e.g. array[80]
3456-- isn't considered a broken identifier.
3457-- "-" is somewhat problematic, but we allow it only as 2nd and up character, so
3458-- there's no ambiguity with unary minus.  (Commands must be separated by spaces
3459-- in CON, so a trailing "-" is "OK", too.)
3460-- This is broken in itself, so we ought to make a compatibility/modern CON switch.
3461local t_broken_identifier = BadIdent(-((tok.number + t_good_identifier) * (sp1 + Set("[]:"))) *
3462                                     (alphanum + Set(BAD_ID_CHARS0)) * (alphanum + Set(BAD_ID_CHARS1))^0)
3463
3464---
3465local function do_flatten_codetab(code, intotab)
3466    for i=1,math.huge do
3467        local elt = code[i]
3468
3469        if (type(elt)=="string") then
3470            intotab[#intotab+1] = elt
3471        elseif (type(elt)=="table") then
3472            do_flatten_codetab(elt, intotab)
3473        else
3474            assert(elt==nil)
3475            return
3476        end
3477    end
3478end
3479
3480-- Return a "string buffer" table that can be table.concat'ed
3481-- to get the code string.
3482local function flatten_codetab(codetab)
3483    local tmpcode = {}
3484    do_flatten_codetab(codetab, tmpcode)
3485    return tmpcode
3486end
3487
3488function on.if_else_end(ifconds, ifstmt, elsestmt, ...)
3489    assert(#{...}==0)
3490    assert(type(ifconds)=="table" and #ifconds>=1)
3491
3492    -- A condition may be a table carrying "deferred" code to add either
3493    --  [1] after the 'if' or
3494    --  [2] after the whole if/else block.
3495    -- In CON, it's always the same code for the same kind of "deferedness",
3496    -- and it's always idempotent (executing it multiple times has the same
3497    -- effect as executing it once), so generate code for it only once, too.
3498    local deferred = { nil, nil }
3499    local linenum = ""
3500
3501    local ifcondstr = {}
3502    for i=1,#ifconds do
3503        local cond = ifconds[i]
3504        local hasmore = type(cond=="table")
3505
3506        ifcondstr[i] = hasmore and cond[1] or cond
3507        assert(type(ifcondstr[i])=="string")
3508
3509        -- IF_LINE_NUMBERING
3510        local tlinum = assert(ifcondstr[i]:match("^.*(%-%-[0-9]+)$"))
3511        ifcondstr[i] = assert(ifcondstr[i]:match("^(.*)%-%-[0-9]+$"))
3512        if (linenum == "") then
3513            linenum = tlinum
3514        end
3515
3516        if (hasmore) then
3517            for i=1,2 do
3518                if (deferred[i]==nil) then
3519                    deferred[i] = cond[i+1]
3520                end
3521            end
3522        end
3523    end
3524
3525    -- Construct a string of ANDed conditions
3526    local conds = "(" .. table.concat(ifcondstr, ")and(") .. ")"
3527
3528    local code = {
3529        format("if %s then%s", conds, linenum),
3530        assert(ifstmt),
3531    }
3532
3533    code[#code+1] = deferred[1]
3534
3535    if (elsestmt~=nil) then
3536        local elseifp = false
3537
3538        if (type(elsestmt)=="table") then
3539            elsestmt = flatten_codetab(elsestmt)
3540
3541            if (#elsestmt>=2 and elsestmt[1]:match("^if ") and elsestmt[#elsestmt]=="end") then
3542                elsestmt[1] = elsestmt[1]:sub(4)
3543                elsestmt[#elsestmt] = nil
3544                elseifp = true
3545            end
3546        end
3547
3548        code[#code+1] = elseifp and "elseif" or "else"
3549        code[#code+1] = elsestmt
3550    end
3551
3552    code[#code+1] = "end"
3553    code[#code+1] = deferred[2]
3554
3555    return code
3556end
3557
3558function on.while_begin(v1, v2)
3559    table.insert(g_isWhile, true)
3560    return format("while (%s~=%s) do", v1, v2)
3561end
3562
3563function on.while_end()
3564    local whilenum = #g_isWhile
3565    table.remove(g_isWhile)
3566    return format("::l%d:: end", whilenum)
3567end
3568
3569function on.switch_begin()
3570    table.insert(g_isWhile, false)
3571end
3572
3573function on.switch_end(testvar, blocks)
3574    local SW = format("_SW[%d]", g_switchCount)
3575    local swcode = { format("%s={", SW) }
3576    local have = {}
3577    local havedefault = false
3578
3579    table.remove(g_isWhile)
3580
3581    for i=1,#blocks do
3582        local block = blocks[i]
3583        assert(#block >= 1)
3584        local isdefault = (#block==1)
3585        local index = isdefault and "'default'" or tostring(block[1])
3586
3587        if (have[index]) then
3588            if (isdefault) then
3589                errprintf("duplicate 'default' block in switch statement")
3590                return "_INVALIDSW()"
3591            else
3592                warnprintf("duplicate case %s in switch statement", index)
3593            end
3594        end
3595        have[index] = true
3596
3597        swcode[#swcode+1] = format("[%s]=function(_aci,_pli,_dist)", index)
3598        swcode[#swcode+1] = get_cache_sap_code()
3599        -- insert the case/default code:
3600        swcode[#swcode+1] = block[#block]
3601        swcode[#swcode+1] = "end,"
3602    end
3603
3604    swcode[#swcode+1] = "}"
3605
3606    -- insert additional case test numbers (e.g. case 0: >>> case 1 <<<: <code...>)
3607    for i=1,#blocks do
3608        local block = blocks[i]
3609        for j=2,#block-1 do
3610            local index = tostring(block[j])
3611            swcode[#swcode+1] = format("%s[%d]=%s[%d]", SW, index, SW, tostring(block[1]))
3612        end
3613    end
3614
3615    assert(g_switchCode ~= nil)
3616    g_switchCode[#g_switchCode+1] = swcode
3617
3618    -- The code for the switch statement itself:
3619    local code = format("_con._switch(_SW[%d], %s, _aci,_pli,_dist)", g_switchCount, testvar)
3620    g_switchCount = g_switchCount+1
3621    return code
3622end
3623
3624function on.case_colon(pos)
3625    pwarnprintf(pos, "encountered deprecated ':' after 'case'")
3626end
3627
3628
3629--- The final grammar!
3630local Grammar = Pat{
3631    -- The starting symbol.
3632    -- A translation unit is a (possibly empty) sequence of outer CON
3633    -- commands, separated by at least one whitespace which may be
3634    -- omitted at the EOF.
3635    sp0 * (all_alt_pattern(Couter, Cblock) * sp1)^0,
3636
3637    -- Some often-used terminals follow.  These appear here because we're
3638    -- hitting a limit with LPeg else.
3639    -- http://lua-users.org/lists/lua-l/2008-11/msg00462.html
3640
3641    -- NOTE: NW demo (NWSNOW.CON) contains a Ctrl-Z char (decimal 26)
3642    whitespace = Set(" \t\r\26") + newline + Set("(),;") + comment + linecomment,
3643
3644    t_number = POS() * lpeg.C(
3645        tok.maybe_minus * ((Pat("0x") + "0X") * Range("09", "af", "AF")^1 * Pat("h")^-1
3646                           + Range("09")^1)
3647                             ) / parse_number,
3648
3649    -- TODO: negated gamevars. Currently, "-var" is parsed as a negated label.
3650
3651    t_identifier_all = lpeg.C(t_broken_identifier + t_good_identifier),
3652    -- NOTE: -conl.keyword alone would be wrong, e.g. "state breakobject":
3653    -- NOTE 2: The + "[" is so that stuff like
3654    --   getactor[THISACTOR].x x
3655    --   getactor[THISACTOR].y y
3656    -- is parsed correctly.  (Compared with this:)
3657    --   getactor[THISACTOR].x x
3658    --   getactor [THISACTOR].y y
3659    -- This is in need of cleanup!
3660    t_identifier = -(conl.keyword * (sp1 + "[")) * tok.identifier_all,
3661    -- TODO?: SST TC has e.g. "1267AT", relying on it to be parsed as a number "1267".
3662    -- However, this conflicts with bad-identifiers, so it should be checked last.
3663    -- This would also handle LNGA2's "00000000h", though would give problems with
3664    -- e.g. "800h" (hex 0x800 or decimal 800?).
3665    t_define = (POS() * lpeg.C(tok.maybe_minus) * tok.identifier / lookup.defined_label) + tok.number,
3666    -- A defined label token, but returning the label if one was passed
3667    -- (specially shoehorned into a string):
3668    t_rawdefine = (POS() * lpeg.C(tok.maybe_minus) * tok.identifier / lookup.raw_defined_label) + tok.number,
3669
3670    -- Defines and constants can take the place of vars that are only read.
3671    -- XXX: now, when tok.rvar fails, the tok.define failure message is printed.
3672    t_rvar = Var("t_botharrayexp") + lpeg.Cmt(tok.identifier, maybe_gamevar_Cmt) + tok.define,
3673    -- For written-to vars, only (non-parm2) array exprs and writable gamevars
3674    -- are permitted.  NOTE: C-CON doesn't support inline array exprs here.
3675    t_wvar = Var("t_singlearrayexp") / function() errprintf("t_wvar: array exprs NYI") return "_NYIVAR" end
3676        + (tok.identifier / function(id) return lookup.gamevar(id, "_aci", true) end),
3677
3678    t_gamearray = Var("t_identifier") / lookup.gamearray,
3679
3680    t_move =
3681        POS()*tok.identifier / function(...) return lookup.composite(LABEL.MOVE, ...) end +
3682        POS()*tok.number / function(...) return check.composite_literal(LABEL.MOVE, ...) end,
3683
3684    t_ai =
3685        POS()*tok.identifier / function(...) return lookup.composite(LABEL.AI, ...) end +
3686        POS()*tok.number / function(...) return check.composite_literal(LABEL.AI, ...) end,
3687
3688    t_action =
3689        POS()*tok.identifier / function(...) return lookup.composite(LABEL.ACTION, ...) end +
3690        POS()*tok.number / function(...) return check.composite_literal(LABEL.ACTION, ...) end,
3691
3692    -- New-style inline arrays and structures.
3693    t_botharrayexp = tok.identifier * arraypat * patt.bothmember^-1
3694        / function(...) return lookup.array_expr(false, ...) end,
3695    t_singlearrayexp = tok.identifier * arraypat * patt.singlemember^-1,
3696
3697    -- SWITCH
3698    switch_stmt = Keyw("switch") * sp1 * tok.rvar * (lpeg.Cc(nil)/on.switch_begin) *
3699        lpeg.Ct((Var("case_block") + Var("default_block"))^0) * sp1 * "endswitch"
3700        / on.switch_end,
3701
3702    -- NOTE: some old DNWMD has "case: PIGCOP".  I don't think I'll allow that.
3703    case_block = lpeg.Ct((sp1 * Keyw("case") * (POS()*Pat(":") / on.case_colon)^-1
3704                         * sp1 * tok.define * (sp0*":")^-1)^1 * sp1 *
3705                         stmt_list_nosp_or_eps), -- * "break",
3706
3707    default_block = lpeg.Ct(sp1 * Keyw("default") * (sp0*":"*sp0 + sp1) *
3708                            stmt_list_nosp_or_eps),  -- * "break",
3709
3710    if_stmt = lpeg.Ct((con_if_begs * sp1)^1) * Var("single_stmt")
3711        * (sp1 * Keyw("else") * sp1 * Var("single_stmt"))^-1 / on.if_else_end,
3712
3713    while_stmt = Keyw("whilevarvarn") * sp1 * tok.rvar * sp1 * tok.rvar / on.while_begin
3714          * sp1 * Var("single_stmt") * (lpeg.Cc(nil) / on.while_end)
3715        + Keyw("whilevarn") * sp1 * tok.rvar * sp1 * tok.define / on.while_begin
3716          * sp1 * Var("single_stmt") * (lpeg.Cc(nil) / on.while_end),
3717
3718    stmt_common = Keyw("{") * sp1 * "}" / ""  -- space separation of commands in CON is for a reason!
3719        -- XXX: this do...end can lead to exceeding Lua nesting limits, see nightstrike's tan.con
3720        + lpeg.Ct(Keyw("{")/"do" * sp1 * stmt_list * sp1 * (Keyw("}")/"end"))
3721        + con_inner_command + Var("switch_stmt") + lpeg.Ct(Var("while_stmt")),
3722
3723    single_stmt = Stmt( lone_else^-1 * (Var("stmt_common") + Var("if_stmt")) ),
3724
3725    -- a non-empty statement/command list
3726    stmt_list = Var("single_stmt") * (sp1 * Var("single_stmt"))^0,
3727}
3728
3729
3730local function setup_newlineidxs(contents)
3731    local newlineidxs = {}
3732    for i in string.gmatch(contents, "()\n") do
3733        newlineidxs[#newlineidxs+1] = i
3734    end
3735    if (#newlineidxs == 0) then
3736        -- try CR only (old Mac)
3737        for i in string.gmatch(contents, "()\r") do
3738            newlineidxs[#newlineidxs+1] = i
3739        end
3740--        if (#newlineidxs > 0) then print('CR-only lineends detected.') end
3741    end
3742    -- dummy newlines at beginning and end
3743    newlineidxs[#newlineidxs+1] = #contents+1
3744    newlineidxs[0] = 0
3745
3746    return newlineidxs
3747end
3748
3749
3750--== Lua -> CON line number mapping for error messages ==--
3751
3752local lineinfo_mt = {
3753    __index = {
3754        -- Get CON file name and CON line number from Lua line number.
3755        getfline = function(self, lualine)
3756            local llines, lfiles = self.llines, self.lfiles
3757            assert(lualine >= 1 and lualine <= #llines)
3758
3759            -- Get the CON line number: a simple lookup.
3760            local conline = llines[lualine]
3761
3762            -- Find the CON file name next.
3763            local confile = nil
3764            for i=1,#lfiles do
3765                if (lfiles[i].line > lualine) then
3766                    break
3767                end
3768                -- Shorten the file name by stripping the directory parts.
3769                confile = lfiles[i].name:match("[^/]+$")
3770            end
3771
3772            return confile or "???", conline
3773        end,
3774    },
3775
3776    __metatable = true,
3777}
3778
3779-- Handle a line of translated CON->Lua code. Return its CON line number.
3780local function lineinfo_handle_line(i, code, curline, curfile, lfiles)
3781    local lnumstr = code:match("%-%-([0-9]+)$")
3782    local begfn = lnumstr and nil or code:match("^%-%- BEGIN (.+)$")
3783    local endfn = lnumstr and nil or code:match("^%-%- END (.+)$")
3784
3785    if (lnumstr) then
3786        curline[#curline] = assert(tonumber(lnumstr))
3787    elseif (begfn) then
3788        curfile[#curfile+1] = begfn
3789        curline[#curline+1] = 1
3790        -- Begin an included file.
3791        lfiles[#lfiles+1] = { line=i, name=begfn }
3792    elseif (endfn) then
3793        assert(endfn==curfile[#curfile])  -- assert proper nesting
3794        curfile[#curfile] = nil
3795        curline[#curline] = nil
3796        -- End an included file, so reset the name to the includer's one.
3797        lfiles[#lfiles+1] = { line=i, name=curfile[#curfile] }
3798    end
3799
3800    return assert(curline[#curline])
3801end
3802
3803-- Construct Lua->CON line mapping info.  This walks the generated code and
3804-- looks for our inserted comment strings, so it's kind of hackish.
3805function get_lineinfo(flatcode)
3806    local curline, curfile = { 0 }, { "<none>" }  -- stacks
3807    -- llines: [<Lua code line number>] = <CON code line number>
3808    -- lfiles: [<sequence number>] = { line=<Lua line number>, name=<filename> }
3809    local llines, lfiles = {}, {}
3810
3811    if (type(flatcode)=="table") then
3812        for i=1,#flatcode do
3813            llines[i] = lineinfo_handle_line(i, flatcode[i], curline, curfile, lfiles)
3814        end
3815    else
3816        -- Already concat'ed code given.
3817        assert(type(flatcode)=="string")
3818        local olinestart = 1
3819
3820        for i=1,math.huge do
3821            local curnli = flatcode:find("\n", olinestart, true)
3822            local line
3823
3824            if (curnli ~= nil) then
3825                line = flatcode:sub(olinestart, curnli-1)
3826                olinestart = curnli+1
3827            else
3828                -- Last line
3829                line = flatcode:sub(olinestart, -1)
3830                break
3831            end
3832
3833            llines[i] = lineinfo_handle_line(i, line, curline, curfile, lfiles)
3834        end
3835    end
3836
3837    return setmetatable({ llines=llines, lfiles=lfiles }, lineinfo_mt)
3838end
3839
3840-- <lineinfop>: Get line info?
3841local function get_code_string(codetab, lineinfop)
3842    -- Create meta-info gamevar: which gamevars have bit NORESET set?
3843    codetab[#codetab+1] = "_V._IS_NORESET_GAMEVAR={"
3844    for identifier, gv in pairs(g_gamevar) do
3845        if (bit.band(gv.flags, GVFLAG.NORESET) ~= 0) then
3846            codetab[#codetab+1] = format("[%q]=true,", identifier)
3847        end
3848    end
3849    codetab[#codetab+1] = "}"
3850
3851    -- Return defined labels in a table...
3852    codetab[#codetab+1] = "return {"
3853    for label, val in pairs(g_labeldef) do
3854        -- ... skipping 'NO' and those that are gamevars in C-CON.
3855        if (g_labeltype[label]==LABEL.NUMBER and not g_labelspecial[label]) then
3856            codetab[#codetab+1] = format("[%q]=%d,", label, val)
3857        end
3858    end
3859    codetab[#codetab+1] = "},_C,_M,_I"  -- CONCODE_RETURN
3860
3861    local flatcode = flatten_codetab(codetab)
3862    local lineinfo = lineinfop and get_lineinfo(flatcode)
3863    return table.concat(flatcode, "\n"), lineinfo
3864end
3865
3866function on.parse_begin()
3867    g_isWhile = {}
3868    g_have_file[g_filename] = true
3869
3870    -- set up new state
3871    -- TODO: pack into one "parser state" table?
3872    g_lastkw, g_lastkwpos, g_numerrors = nil, nil, 0
3873    g_recurslevel = g_recurslevel+1
3874end
3875
3876
3877---=== EXPORTED FUNCTIONS ===---
3878
3879function parse(contents)  -- local
3880    -- save outer state
3881    local lastkw, lastkwpos, numerrors = g_lastkw, g_lastkwpos, g_numerrors
3882    local newlineidxs = g_newlineidxs
3883
3884    on.parse_begin()
3885
3886    g_newlineidxs = setup_newlineidxs(contents)
3887
3888    addcodef("-- BEGIN %s", g_filename)
3889
3890    local idx = lpeg.match(Grammar, contents)
3891
3892    if (not idx) then
3893        printf("[%d] Match failed.", g_recurslevel)
3894        g_numerrors = inf
3895    elseif (idx == #contents+1) then
3896        if (g_numerrors ~= 0) then
3897            printf("[%d] Matched whole contents (%d errors).",
3898                   g_recurslevel, g_numerrors)
3899        elseif (g_recurslevel==0) then
3900            printf("[0] Matched whole contents.")
3901        end
3902    else
3903        local i, col = getlinecol(idx)
3904        local bi, ei = g_newlineidxs[i-1]+1, g_newlineidxs[i]-1
3905
3906        printf("[%d] Match succeeded up to line %d, col %d (pos=%d, len=%d)",
3907               g_recurslevel, i, col, idx, #contents)
3908        g_numerrors = inf
3909
3910--        printf("Line goes from %d to %d", bi, ei)
3911        local suffix = ""
3912        if (ei-bi > 76) then
3913            ei = bi+76
3914            suffix = " (...)"
3915        end
3916        printf("%s%s", string.sub(contents, bi, ei), suffix)
3917
3918        if (g_lastkwpos) then
3919            i, col = getlinecol(g_lastkwpos)
3920            printf("Last keyword was at line %d, col %d: %s", i, col, g_lastkw)
3921        end
3922    end
3923
3924    -- Check read/written status of all user gamevars.
3925    if (idx == #contents+1 and g_recurslevel==0) then
3926        local gvs = {}
3927        for identifier, gv in pairs(g_gamevar) do
3928            if (gv.used ~= 3) then
3929                -- NOTE: read but not written to gamevar (gv.used == 1) has its
3930                -- use in C-CON
3931                if (gv.used == 0 and g_warn["never-used-gamevar"] or
3932                        gv.used == 2 and g_warn["never-read-gamevar"]) then
3933                    gv.id = identifier
3934                    gvs[#gvs+1] = gv
3935                end
3936            end
3937        end
3938
3939        local function compare_gv(gva, gvb)
3940            if (gva.loc[1] ~= gvb.loc[1]) then
3941                return gva.loc[1] < gvb.loc[1]
3942            end
3943            return (gva.loc[2] < gvb.loc[2])
3944        end
3945
3946        table.sort(gvs, compare_gv)
3947
3948        for i=1,#gvs do
3949            local gv = gvs[i]
3950
3951            local loc = gv.loc
3952            local locstr = loc and format("%s %d:%d: ", loc[1], loc[2], loc[3]) or ""
3953
3954            local perActor = (bit.band(gv.flags, GVFLAG.PERACTOR) ~= 0)
3955            local perPlayer = (bit.band(gv.flags, GVFLAG.PERPLAYER) ~= 0)
3956            local kindstr = perActor and "per-actor " or (perPlayer and "per-player " or "")
3957
3958            if (gv.used == 0) then
3959                printf("%sWarning: never used %sgamevar `%s'", locstr,
3960                       kindstr, gv.id)
3961            else
3962                printf("%sWarning: never %s %sgamevar `%s'", locstr,
3963                       gv.used == 1 and "written to" or "read",
3964                       kindstr, gv.id)
3965            end
3966        end
3967    end
3968
3969    addcodef("-- END %s", g_filename)
3970    g_recurslevel = g_recurslevel-1
3971
3972    -- restore outer state
3973    g_lastkw, g_lastkwpos = lastkw, lastkwpos
3974    g_numerrors = math.max(g_numerrors, numerrors)
3975    g_newlineidxs = newlineidxs
3976end
3977
3978function reset.all()
3979    reset.labels()
3980    reset.gamedata()
3981    reset.codegen()
3982end
3983
3984local function print_on_failure(msg)
3985    if (g_lastkwpos ~= nil) then
3986        printf("LAST KEYWORD POSITION: %s, %s", linecolstr(g_lastkwpos), g_lastkw)
3987    end
3988    print(msg)
3989end
3990
3991if (string.dump) then
3992    -- running stand-alone
3993    local io = require("io")
3994
3995    local function compile(filename)
3996        reset.all()
3997
3998        -- Construct file name for the output code: (...)/xxx/qwe.con -->
3999        -- xxx_qwe.con, so that common root CON file names like EDUKE.CON will
4000        -- result in distinct file names for different mods. From that name,
4001        -- strip the extension.
4002        local codedir = g_cgopt["gendir"]
4003        local codefn = codedir and
4004            codedir.."/"..filename:match("[^/]+/[^/]+$"):gsub('/','_')..".lua"
4005
4006        -- Get the directory part...
4007        g_directory = filename:match(".*/") or ""
4008        -- ...and the file name alone.
4009        filename = filename:sub(#g_directory+1, -1)
4010
4011        -- NOTE: xpcall isn't useful here since the traceback won't give us
4012        -- anything inner to the lpeg.match call
4013        local ok, msg = pcall(do_include_file, g_directory, filename, true)
4014        -- ^v Swap commenting (comment top, uncomment bottom line) to get backtraces
4015--        local ok, msg = true, do_include_file(g_directory, filename, true)
4016
4017        if (not ok) then
4018            print_on_failure(msg)
4019        end
4020
4021        if (not (g_cgopt["no"]==true)) then
4022            local onlycheck = (g_cgopt["no"] == "onlycheck")
4023            -- The file for the output messages:
4024            local msgfile = onlycheck and io.stdout or io.stderr
4025
4026            local code, lineinfo = get_code_string(g_curcode, g_cgopt["debug-lineinfo"])
4027            local func, errmsg = loadstring(code, "CON")
4028
4029--            msgfile:write(format("-- GENERATED CODE for \"%s\":\n", filename))
4030            if (func == nil) then
4031                msgfile:write(format("-- %s%s: INVALID Lua CODE: %s\n",
4032                                     g_directory, filename, errmsg))
4033            end
4034
4035            if (g_cgopt["names"]) then
4036                for i=0,C.MAXTILES-1 do
4037                    if (g_actorTileToName[i]) then
4038                        msgfile:write(format("#define %s %d\n", g_actorTileToName[i], i))
4039                    end
4040                end
4041            elseif (lineinfo) then
4042                for i=1,#lineinfo.llines do
4043                    msgfile:write(format("%d -> %s:%d\n", i, lineinfo:getfline(i)))
4044                end
4045            elseif (not onlycheck) then
4046                -- The file for the generated code:
4047                local codefile = codefn and assert(io.open(codefn, "w+")) or msgfile
4048
4049                codefile:write(code)
4050                codefile:write("\n")
4051            end
4052        end
4053    end
4054
4055    local havelists = false
4056
4057    for argi=1,#arg do
4058        local filename = arg[argi]
4059
4060        if (filename=="@") then
4061            -- Start file list processing from the next positional argument on.
4062            havelists = true
4063        elseif (havelists) then
4064            printf("\n------ Handling list of CON files \"%s\"", filename)
4065            for fn in io.lines(filename) do
4066                -- A hash at the beginning of a line denotes a comment, an
4067                -- empty line is skipped.
4068                if (#fn>0 and not fn:match("^#")) then
4069                    compile(fn)
4070                end
4071            end
4072        else
4073            compile(filename)
4074        end
4075    end
4076else
4077    -- running from EDuke32
4078
4079    function compile(filenames)
4080        -- TODO: pathsearchmode=1 set in G_CompileScripts
4081
4082        reset.all()
4083
4084        for _, fname in ipairs(filenames) do
4085            local ok, msg = pcall(do_include_file, "", fname, true)
4086            if (not ok or g_numerrors > 0) then
4087                if (not ok) then
4088                    -- Unexpected error in the Lua code (i.e. a bug here).
4089                    print_on_failure(msg)
4090                end
4091                return nil
4092            end
4093        end
4094
4095        return get_code_string(g_curcode, true)
4096    end
4097end
4098