Engage Cmd Scripting With Lua - rallytac/pub GitHub Wiki

WORK IN PROGRESS !!!

Scripting Engage-Cmd with Lua

Engage-Cmd (engage-cmd) is a command-line tool hosting an Engage Engine and typically runs in an operating system console/terminal environment. You can pass parameters on the invocation command-line to engage-cmd, instruct it to perform operations while in interactive mode once engage-cmd is running, or script your operations using the Lua language. In this document we will concern ourselves with using Lua as the scripting language.

To fire up engage-cmd and get it to run your script you need some basic command-line parameters to get things going. These parameters include the certificate store, the engine policy, and the mission configuration.

$ engage-cmd -cs:<certificate_store_file> -ep:<engine_policy_file> -mission:<mission_file> -script:<lua_script_file>

Hello World!

Let's say we have a simple "hello world" script - let's call it "hello.lua" - as follows:

print('hello world')

To run this with a certificate store named all-rts-certs.certstore, a policy file name ep.json, and a mission file named m1.json; do the following:

$ engage-cmd -cs:all-rts-certs.certstore -ep:ep.json -mission:m1.json -script:hello.lua

A Little More Meat

Of course, just printing "hello world" is not going to do a whole lot for us. So let's look at something a little more useful. Let's say we have a Lua script that sets up all the groups in our mission and, once that's done, we'll transmit for 5 seconds on the first audio group.

-- Create all the groups ("-1" means "all groups")
ecCreateGroup(-1)

-- Join all those groups
ecJoinGroup(-1)

-- Wait for all of them to be ready
ecWaitForGroupReady(-1)

-- Begin transmission on group 1 - which we know is the index of the first audio group
ecBeginGroupTx(1)

-- Pause for 5 seconds - we should be transmitting by now so let that go on for 5 second (5,000 milliseconds)
ecSleep(5000)

-- End the transmission on group 1
ecEndGroupTx(1)

What'll happen here is that all the groups in the mission will be created, followed right away by them all being joined. Now, the Engage Engine does all this stuff asynchronously so we have to wait until things are ready to rock and roll before we continue. So, we call ecWaitForGroup() and wait for it to come back. For all of these calls we've specified -1 as the group index which engage-cmd interprets as "all groups" rather than a specific group index.

Then, once we're ready, we tell engage-cmd to begin transmission on group 1 (not -1!!), we then pause for a few seconds by calling ecSleep(), and then finish off by calling ecEndGroupTx() to stop transmission. Pretty straight forward, huh!?

A Teeny-Weeny Load Generator

OK, we've got the basics done so no we can play around with Lua a little more to write a script that'll exercise things a little more and end up with a nice little load-generator script.

ecCreateGroup(-1)
ecJoinGroup(-1)
ecWaitForGroupReady(-1)

-- We'll transmit on group 1 for up to 5 seconds at a time.  We'll do this
-- 250 times, pausing 2 seconds between iterations.
for x = 1, 250 do
        ecBeginGroupTx(1)
        ecWaitForGroupTxStarted(1)
        ecLogInfo('..................... began transmission')
    
        ecSleep(math.random(1000, 5000))
    
        ecEndGroupTx(1)
        ecWaitForGroupTxEnded(1)
        ecLogInfo('..................... ended transmission')
    
        ecSleep(2000)
end

A Teeny-Weeny Load Generator v2

Our load generator above is going to transmit whatever it captures from the device microphone. Maybe we don't want that. Maybe we want to transmit some cool 70's disco music or poetry reading by James Earl Jones (who could POSSIBLY say no to that!?). So, let's use the ecSetTxUri() function to transmit from an audio file.

-- Up front, set the "transmit URI" for all audio groups to our awesome James Earl Jones poetry reading with
-- a repeat count of 0
ecSetTxUri(0, '/mysounds/jej-poetry-slam.wav')

ecCreateGroup(-1)
ecJoinGroup(-1)
ecWaitForGroupReady(-1)

-- We'll transmit on group 1 between 20 and 25 seconds at a time so we get to hear more of
-- that terrific voice
for x = 1, 250 do
        ecBeginGroupTx(1)
        ecWaitForGroupTxStarted(1)
    
        ecSleep(math.random(20000, 25000))
    
        ecEndGroupTx(1)
        ecWaitForGroupTxEnded(1)
    
        ecSleep(2000)
end

Logging

Logging functions allow for the Lua script to log messages using the Engine's logging subsystem. This means that any logging done with these functions will not only be synchronized with the rest of the logging system but also be directed to the same outputs as the rest of Engage's logging. In addition, log lines are colorized on supported ANSI-compatible terminals as well as being able to be filtered based on logging levels, thread identifiers, component tags, and so on.

Function Description Return Type:<value> Comments
ecLogFatal(msg) Log a fatal message void
ecLogError(msg) Log an error message void
ecLogWarn(msg) Log a warning message void
ecLogInfo(msg) Log an informational message void
ecLogDebug(msg) Log a debug message void

Engine Operations

These functions operate on the Engage Engine

Function Description Return Type:<value> Comments
ecStartEngine() Starts the Engine void beta
ecStopEngine() Starts the Engine void beta
ecRestartEngine() Restarts the Engine void beta
ecReinitEngine() Reinitializes the Engine void beta

Group Operations

These functions operate on the Engage groups specified in the -mission command-line parameter.

Function Description Return Type:<value> Comments
ecGetGroupCount() Return the number of groups defined in the current mission integer
ecGetGroupId(index) Return the group ID for index string
ecGetGroupName(index) Return the group name for index string
ecGetGroupJson(index) Return the JSON configuration for index string
ecSetGroupJson(index, json) Sets the JSON configuration for index void Changing the JSON for an already-created group has no effect until that group is (re)created.
ecGetGroupType(index) Return the Engage group type for index integer: 1 for audio, 2 for presence, 3 for raw
ecIsGroupTypeAudio(index) Tests whether the group type for index is audio boolean
ecIsGroupTypePresence(index) Tests whether the group type for index is presence boolean
ecIsGroupTypeRaw(index) Tests whether the group type for index is raw boolean
ecIsGroupCreated(index) Tests whether the group for index has been created boolean -1 tests all groups
ecIsGroupJoined(index) Tests whether the group for index has been joined boolean -1 tests all groups
ecIsGroupConnected(index) Tests whether the group for index has been connected boolean -1 tests all groups
ecIsGroupReady(index) Tests whether the group for index is ready - i.e. created, joined, and connected boolean -1 tests all groups
ecWaitForGroupReady(index) Waits until the group for index is ready - i.e. created, joined, and connected boolean -1 waits for all groups to be ready
ecIsGroupTxStarted(index) Returns true if TX has started for audio group index boolean -1 tests all audio groups and returns true if all group TX has started
ecIsGroupTxFailed(index) Returns true if TX has failed for audio group index boolean -1 tests all audio groups and returns true if any group TX has failed
ecIsGroupTxEnded(index) Returns true if TX has ended for audio group index boolean -1 tests all audio groups and returns true if all group TX has ended
ecWaitForGroupTxStarted(index) Waits until the group for index has begun TX boolean -1 waits for all groups to begin TX
ecWaitForGroupTxEnded(index) Waits until the group for index has ended TX or TX failure boolean -1 waits for all groups' TX to end or TX failure on any group
ecCreateGroup(index) Creates group for index void -1 creates all groups
ecDeleteGroup(index) Deletes group for index void -1 deletes all groups
ecJoinGroup(index) Joins group for index void -1 joins all groups
ecLeaveGroup(index) Leaves group for index void -1 leaves all groups
ecBeginGroupTx(index) Begins TX on audio group for index void -1 begins TX on all audio groups
ecEndGroupTx(index) End TX on audio group for index void -1 end TX on all audio groups
ecMuteGroupRx(index) Mutes RX on audio group for index void -1 mutes RX on all audio groups
ecUnmuteGroupRx(index) Unmutes RX on audio group for index void -1 unmutes RX on all audio groups
ecMuteGroupTx(index) Mutes TX on audio group for index void -1 mutes TX on all audio groups
ecUnmuteGroupTx(index) Unmutes TX on audio group for index void -1 unmutes TX on all audio groups
ecSetTxPriority(priority) Sets the priority (0 - 255) to be used for audio TX void Applies to TX on all audio groups
ecSetTxFlags(flags) Sets the flags (16-bit value) to be used for audio TX void Applies to TX on all audio groups

Miscellaneous

Function Description Return Type:<value> Comments
ecSleep(ms) Pause operation for ms milliseconds void
ecSetExitCode(exitCode) Sets the process exit code void Sets the integer value for engage-cmd to return to the calling process upon completion
ecSetTxUri(repeatCount, uri) Sets the name of the file to TX and the number of times to repeat void repeatCount of 0 transmits the file once, a value of -1 will repeat indefinitely; uri must be the path name to a locally accessible raw audio file containing only linear PCM, signed 16-bit samples, with a sampling rate and number of channels matching the Engine's currently configured internal audio processing settings
ecGetRandom64() Returns a random 64-bit number unsigned 64-bit number
ecGetTickMs() Returns a 64-bit number representing an incrementing counter value in milliseconds unsigned 64-bit number This number generally represents the number of millisecond increments the operating system has incurred on its monotonic clock since startup. However, it is operating system dependent and you should not expect it to necessarily start at zero nor be representative of a wallclock time such as a Unix timestamp.
ecGetWaitingKeyboardInput() Returns any queued input from stdin string If no input is currently queued, returns nil or an empty string. This funtion does NOT wait for user input. Rather, it checks the input queue, reads anything that may be present and return immediately.

One of our internal test scripts

Alright, how's about we share some Lua code we use internally here at RTS ... ? Here's a pretty good one (albeit a little edited). This script does a load test on the Engage Engine by transmitting on each group in a mission using a combination of every codec we support at every framing rate we support. While we're primarily interested in verifiying audio transmission and receipt (our mission is full-duplex in nature so all endpoints can be talking a huge amount of the time) for different codecs, we're also getting a nice bonus of testing Engage's functionality to create and delete groups on the fly through reconfiguration. We typically run this script on around 50 instances of engage-cmd to really beat up on all the Engines across a variety of OS platforms (Mac, Linux, Windows, Raspberry, Embedded Linux, etc). While we don't expect you to do the same, it's a pretty good example of the kind of testing we do ... and shows off Lua scripting rather nicely.

----------------------------------------------------------------------
-- codectester.lua
--
-- Copyright (c) 2021 Rally Tactical Systems, Inc.
--
-- Permission is hereby granted, free of charge, to any person obtaining a copy of
-- this software and associated documentation files (the "Software"), to deal in
-- the Software without restriction, including without limitation the rights to
-- use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies
-- of the Software, and to permit persons to whom the Software is furnished to do
-- so, subject to the following conditions:
--
-- The above copyright notice and this permission notice shall be included in all
-- copies or substantial portions of the Software.
--
-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
-- IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
-- FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
-- AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
-- LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
-- OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
-- SOFTWARE.
----------------------------------------------------------------------

-- Lua needs to know where to find sources ...
package.path = package.path .. ';../?.lua'

-- Like the json.lua package (see below)
json = require "../json"
os = require "os"

-- Setup some constants (our convention is to make constants all uppercase)
GROUP_TYPE_AUDIO = 1
GROUP_TYPE_PRESENCE = 2
GROUP_TYPE_RAW = 3

GRP_ITERATIONS = 1
GRP_INTERVAL = 500

PTT_ITERATIONS = 2
PTT_TIME = 500
PTT_INTERVAL = 100

-- Our global variables
endOfOperation = false
audioGroups = {}
presenceGroups = {}
rawGroups = {}

-- The codec types (actually the encoders) that Engage supports
codecs = {
        1, 2, 3, 
        10, 11, 12, 13, 14, 15, 16, 17, 
        20, 21, 22, 23, 24, 25, 26, 27, 28, 29,
        30, 31, 32, 33, 34, 35, 36, 37
        }

-- A table of possible framing sizes we'll throw at Engage
framings = {20, 40, 60, 80, 100, 120, 140, 160 }

-- Get the count of groups in the mission
totalGroupCount = ecGetGroupCount()


-- Returns true if a string is nil or ""
function isEmpty(s)
	return s == nil or s == ""
end


-- Divides the groups from the mission into different Lua tables
function setupTables() 
  for x = 1, totalGroupCount, 1 do
    if ecGetGroupType(x - 1) == GROUP_TYPE_AUDIO then
      table.insert(audioGroups, x - 1)

    elseif ecGetGroupType(x - 1) == GROUP_TYPE_PRESENCE then
        table.insert(presenceGroups, x - 1)

    elseif ecGetGroupType(x - 1) == GROUP_TYPE_RAW then
      table.insert(rawGroups, x - 1)

    end
  end
end


-- Returns true if this script should stop
function shouldEndOperation()
  if endOperation then
    return true
  end

  str = ecGetWaitingKeyboardInput()
  if not isEmpty(str) then    
    if str == "q" then
      endOperation = true
    end
  end

  return endOperation
end


-- Try out an encoder and framing combination for a group
function tryThisForCodecTest(groupIndex, encoder, framing)
  -- Get the name of the group for display purposes
  groupName = ecGetGroupName(groupIndex)

  -- Get the group's JSON configiguration
  gc = ecGetGroupJson(groupIndex)

  -- Decode the JSON into a Lua table
  obj = json.decode(gc)

  -- Set the encoder and framing size
  obj["txAudio"]["encoder"] = encoder
  obj["txAudio"]["framingMs"] = framing
  
  -- Encode the JSON (serialize) to a string and set the JSON in the group object
  ecSetGroupJson(groupIndex, json.encode(obj))

  for grpI = 1, GRP_ITERATIONS, 1 do
    if shouldEndOperation() then
      break
    end

    -- Create the group (using the JSON we set above)
    ecCreateGroup(groupIndex)

    -- Join it
    ecJoinGroup(groupIndex)  

    -- Wait for it to be ready (i.e. created, joined, and connected)
    ecWaitForGroupReady(groupIndex)

    -- Hammer away a little on PTT
    for pttI = 1, PTT_ITERATIONS, 1 do
      if shouldEndOperation() then
        break
      end

      -- Print out a message so we know where we are
      ecLogInfo(groupName 
                 .. ", enc:" .. encoder 
                 .. ", fra:" .. framing 
                 .. ", g:" .. grpI .. "/" .. GRP_ITERATIONS 
                 .. ", p:" .. pttI .. "/" .. PTT_ITERATIONS)

      -- Start transmitting
      ecBeginGroupTx(groupIndex)

      -- Keep transmitting for PTT_TIME
      ecSleep(PTT_TIME)

      -- Stop
      ecEndGroupTx(groupIndex)

      -- Wait until PTT has ended
      ecWaitForGroupTxEnded(groupIndex)

      -- Pause a little
      ecSleep(PTT_INTERVAL)
    end

    -- Delete the group
    ecDeleteGroup(groupIndex)

    -- Pause a little
    ecSleep(GRP_INTERVAL)
  end
end


-- Our "main" operation here
function mainForCodecTest()
  -- Make sure we actually have audio groups configured
  if #audioGroups > 0 then

    -- For each group ...
    for g = 1, #audioGroups, 1 do      

      -- .. for each codec ..
      for e = 1, #codecs, 1 do
        -- .. for each framing ..

        for f = 1, #framings, 1 do
          if shouldEndOperation() then
            break            
           end

          -- .. try the combination
          tryThisForCodecTest(audioGroups[g], codecs[e], framings[f], 0)
        end -- f

      end -- e

    end -- g

  else
    ecLogFatal("No audio groups found")
  end
end 


-- Get on to all the presence groups so that any apps monitoring this business can see what's going on
function getOnAllPresenceGroups()
  for x = 1, #presenceGroups, 1 do
    ecCreateGroup(presenceGroups[x])
    ecJoinGroup(presenceGroups[x])    
  end
end 


-- MAIN --------------------------------------------------------------
math.randomseed(ecGetRandom64())
setupTables()
getOnAllPresenceGroups()
mainForCodecTest()

json.lua

Here's a really neat little add-on (in Lua source) that makes it pretty straightforward to conduct basic JSON operations in Lua.

--
-- json.lua
--
-- Copyright (c) 2020 rxi
--
-- Permission is hereby granted, free of charge, to any person obtaining a copy of
-- this software and associated documentation files (the "Software"), to deal in
-- the Software without restriction, including without limitation the rights to
-- use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies
-- of the Software, and to permit persons to whom the Software is furnished to do
-- so, subject to the following conditions:
--
-- The above copyright notice and this permission notice shall be included in all
-- copies or substantial portions of the Software.
--
-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
-- IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
-- FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
-- AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
-- LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
-- OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
-- SOFTWARE.
--

local json = { _version = "0.1.2" }

-------------------------------------------------------------------------------
-- Encode
-------------------------------------------------------------------------------

local encode

local escape_char_map = {
  [ "\\" ] = "\\",
  [ "\"" ] = "\"",
  [ "\b" ] = "b",
  [ "\f" ] = "f",
  [ "\n" ] = "n",
  [ "\r" ] = "r",
  [ "\t" ] = "t",
}

local escape_char_map_inv = { [ "/" ] = "/" }
for k, v in pairs(escape_char_map) do
  escape_char_map_inv[v] = k
end


local function escape_char(c)
  return "\\" .. (escape_char_map[c] or string.format("u%04x", c:byte()))
end


local function encode_nil(val)
  return "null"
end


local function encode_table(val, stack)
  local res = {}
  stack = stack or {}

  -- Circular reference?
  if stack[val] then error("circular reference") end

  stack[val] = true

  if rawget(val, 1) ~= nil or next(val) == nil then
    -- Treat as array -- check keys are valid and it is not sparse
    local n = 0
    for k in pairs(val) do
      if type(k) ~= "number" then
        error("invalid table: mixed or invalid key types")
      end
      n = n + 1
    end
    if n ~= #val then
      error("invalid table: sparse array")
    end
    -- Encode
    for i, v in ipairs(val) do
      table.insert(res, encode(v, stack))
    end
    stack[val] = nil
    return "[" .. table.concat(res, ",") .. "]"

  else
    -- Treat as an object
    for k, v in pairs(val) do
      if type(k) ~= "string" then
        error("invalid table: mixed or invalid key types")
      end
      table.insert(res, encode(k, stack) .. ":" .. encode(v, stack))
    end
    stack[val] = nil
    return "{" .. table.concat(res, ",") .. "}"
  end
end


local function encode_string(val)
  return '"' .. val:gsub('[%z\1-\31\\"]', escape_char) .. '"'
end


local function encode_number(val)
  -- Check for NaN, -inf and inf
  if val ~= val or val <= -math.huge or val >= math.huge then
    error("unexpected number value '" .. tostring(val) .. "'")
  end
  return string.format("%.14g", val)
end


local type_func_map = {
  [ "nil"     ] = encode_nil,
  [ "table"   ] = encode_table,
  [ "string"  ] = encode_string,
  [ "number"  ] = encode_number,
  [ "boolean" ] = tostring,
}


encode = function(val, stack)
  local t = type(val)
  local f = type_func_map[t]
  if f then
    return f(val, stack)
  end
  error("unexpected type '" .. t .. "'")
end


function json.encode(val)
  return ( encode(val) )
end


-------------------------------------------------------------------------------
-- Decode
-------------------------------------------------------------------------------

local parse

local function create_set(...)
  local res = {}
  for i = 1, select("#", ...) do
    res[ select(i, ...) ] = true
  end
  return res
end

local space_chars   = create_set(" ", "\t", "\r", "\n")
local delim_chars   = create_set(" ", "\t", "\r", "\n", "]", "}", ",")
local escape_chars  = create_set("\\", "/", '"', "b", "f", "n", "r", "t", "u")
local literals      = create_set("true", "false", "null")

local literal_map = {
  [ "true"  ] = true,
  [ "false" ] = false,
  [ "null"  ] = nil,
}


local function next_char(str, idx, set, negate)
  for i = idx, #str do
    if set[str:sub(i, i)] ~= negate then
      return i
    end
  end
  return #str + 1
end


local function decode_error(str, idx, msg)
  local line_count = 1
  local col_count = 1
  for i = 1, idx - 1 do
    col_count = col_count + 1
    if str:sub(i, i) == "\n" then
      line_count = line_count + 1
      col_count = 1
    end
  end
  error( string.format("%s at line %d col %d", msg, line_count, col_count) )
end


local function codepoint_to_utf8(n)
  -- http://scripts.sil.org/cms/scripts/page.php?site_id=nrsi&id=iws-appendixa
  local f = math.floor
  if n <= 0x7f then
    return string.char(n)
  elseif n <= 0x7ff then
    return string.char(f(n / 64) + 192, n % 64 + 128)
  elseif n <= 0xffff then
    return string.char(f(n / 4096) + 224, f(n % 4096 / 64) + 128, n % 64 + 128)
  elseif n <= 0x10ffff then
    return string.char(f(n / 262144) + 240, f(n % 262144 / 4096) + 128,
                       f(n % 4096 / 64) + 128, n % 64 + 128)
  end
  error( string.format("invalid unicode codepoint '%x'", n) )
end


local function parse_unicode_escape(s)
  local n1 = tonumber( s:sub(1, 4),  16 )
  local n2 = tonumber( s:sub(7, 10), 16 )
   -- Surrogate pair?
  if n2 then
    return codepoint_to_utf8((n1 - 0xd800) * 0x400 + (n2 - 0xdc00) + 0x10000)
  else
    return codepoint_to_utf8(n1)
  end
end


local function parse_string(str, i)
  local res = ""
  local j = i + 1
  local k = j

  while j <= #str do
    local x = str:byte(j)

    if x < 32 then
      decode_error(str, j, "control character in string")

    elseif x == 92 then -- `\`: Escape
      res = res .. str:sub(k, j - 1)
      j = j + 1
      local c = str:sub(j, j)
      if c == "u" then
        local hex = str:match("^[dD][89aAbB]%x%x\\u%x%x%x%x", j + 1)
                 or str:match("^%x%x%x%x", j + 1)
                 or decode_error(str, j - 1, "invalid unicode escape in string")
        res = res .. parse_unicode_escape(hex)
        j = j + #hex
      else
        if not escape_chars[c] then
          decode_error(str, j - 1, "invalid escape char '" .. c .. "' in string")
        end
        res = res .. escape_char_map_inv[c]
      end
      k = j + 1

    elseif x == 34 then -- `"`: End of string
      res = res .. str:sub(k, j - 1)
      return res, j + 1
    end

    j = j + 1
  end

  decode_error(str, i, "expected closing quote for string")
end


local function parse_number(str, i)
  local x = next_char(str, i, delim_chars)
  local s = str:sub(i, x - 1)
  local n = tonumber(s)
  if not n then
    decode_error(str, i, "invalid number '" .. s .. "'")
  end
  return n, x
end


local function parse_literal(str, i)
  local x = next_char(str, i, delim_chars)
  local word = str:sub(i, x - 1)
  if not literals[word] then
    decode_error(str, i, "invalid literal '" .. word .. "'")
  end
  return literal_map[word], x
end


local function parse_array(str, i)
  local res = {}
  local n = 1
  i = i + 1
  while 1 do
    local x
    i = next_char(str, i, space_chars, true)
    -- Empty / end of array?
    if str:sub(i, i) == "]" then
      i = i + 1
      break
    end
    -- Read token
    x, i = parse(str, i)
    res[n] = x
    n = n + 1
    -- Next token
    i = next_char(str, i, space_chars, true)
    local chr = str:sub(i, i)
    i = i + 1
    if chr == "]" then break end
    if chr ~= "," then decode_error(str, i, "expected ']' or ','") end
  end
  return res, i
end


local function parse_object(str, i)
  local res = {}
  i = i + 1
  while 1 do
    local key, val
    i = next_char(str, i, space_chars, true)
    -- Empty / end of object?
    if str:sub(i, i) == "}" then
      i = i + 1
      break
    end
    -- Read key
    if str:sub(i, i) ~= '"' then
      decode_error(str, i, "expected string for key")
    end
    key, i = parse(str, i)
    -- Read ':' delimiter
    i = next_char(str, i, space_chars, true)
    if str:sub(i, i) ~= ":" then
      decode_error(str, i, "expected ':' after key")
    end
    i = next_char(str, i + 1, space_chars, true)
    -- Read value
    val, i = parse(str, i)
    -- Set
    res[key] = val
    -- Next token
    i = next_char(str, i, space_chars, true)
    local chr = str:sub(i, i)
    i = i + 1
    if chr == "}" then break end
    if chr ~= "," then decode_error(str, i, "expected '}' or ','") end
  end
  return res, i
end


local char_func_map = {
  [ '"' ] = parse_string,
  [ "0" ] = parse_number,
  [ "1" ] = parse_number,
  [ "2" ] = parse_number,
  [ "3" ] = parse_number,
  [ "4" ] = parse_number,
  [ "5" ] = parse_number,
  [ "6" ] = parse_number,
  [ "7" ] = parse_number,
  [ "8" ] = parse_number,
  [ "9" ] = parse_number,
  [ "-" ] = parse_number,
  [ "t" ] = parse_literal,
  [ "f" ] = parse_literal,
  [ "n" ] = parse_literal,
  [ "[" ] = parse_array,
  [ "{" ] = parse_object,
}


parse = function(str, idx)
  local chr = str:sub(idx, idx)
  local f = char_func_map[chr]
  if f then
    return f(str, idx)
  end
  decode_error(str, idx, "unexpected character '" .. chr .. "'")
end


function json.decode(str)
  if type(str) ~= "string" then
    error("expected argument of type string, got " .. type(str))
  end
  local res, idx = parse(str, next_char(str, 1, space_chars, true))
  idx = next_char(str, idx, space_chars, true)
  if idx <= #str then
    decode_error(str, idx, "trailing garbage")
  end
  return res
end


return json
⚠️ **GitHub.com Fallback** ⚠️