1
0
mirror of https://github.com/nmap/nmap.git synced 2025-12-06 04:31:29 +00:00

Merged Lpeg branch

This commit is contained in:
devin
2014-06-26 20:12:54 +00:00
parent 9fe9545d49
commit d68396d823
16 changed files with 6128 additions and 3700 deletions

View File

@@ -86,9 +86,9 @@ UNINSTALLZENMAP=@UNINSTALLZENMAP@
UNINSTALLNPING=@UNINSTALLNPING@ UNINSTALLNPING=@UNINSTALLNPING@
ifneq (@LIBLUA_LIBS@,) ifneq (@LIBLUA_LIBS@,)
NSE_SRC=nse_main.cc nse_utility.cc nse_nsock.cc nse_dnet.cc nse_fs.cc nse_nmaplib.cc nse_debug.cc nse_pcrelib.cc nse_binlib.cc nse_bit.cc NSE_SRC=nse_main.cc nse_utility.cc nse_nsock.cc nse_dnet.cc nse_fs.cc nse_nmaplib.cc nse_debug.cc nse_pcrelib.cc nse_binlib.cc nse_bit.cc nse_lpeg.cc
NSE_HDRS=nse_main.h nse_utility.h nse_nsock.h nse_dnet.h nse_fs.h nse_nmaplib.h nse_debug.h nse_pcrelib.h nse_binlib.h nse_bit.h NSE_HDRS=nse_main.h nse_utility.h nse_nsock.h nse_dnet.h nse_fs.h nse_nmaplib.h nse_debug.h nse_pcrelib.h nse_binlib.h nse_bit.h nse_lpeg.h
NSE_OBJS=nse_main.o nse_utility.o nse_nsock.o nse_dnet.o nse_fs.o nse_nmaplib.o nse_debug.o nse_pcrelib.o nse_binlib.o nse_bit.o NSE_OBJS=nse_main.o nse_utility.o nse_nsock.o nse_dnet.o nse_fs.o nse_nmaplib.o nse_debug.o nse_pcrelib.o nse_binlib.o nse_bit.o nse_lpeg.o
ifneq (@OPENSSL_LIBS@,) ifneq (@OPENSSL_LIBS@,)
NSE_SRC+=nse_openssl.cc nse_ssl_cert.cc NSE_SRC+=nse_openssl.cc nse_ssl_cert.cc
NSE_HDRS+=nse_openssl.h nse_ssl_cert.h NSE_HDRS+=nse_openssl.h nse_ssl_cert.h

4648
libpcre/configure vendored

File diff suppressed because it is too large Load Diff

3706
lpeg.c Normal file

File diff suppressed because it is too large Load Diff

7
nse_lpeg.cc Normal file
View File

@@ -0,0 +1,7 @@
extern "C" {
#include "lauxlib.h"
#include "lua.h"
}
#include "lpeg.c"

8
nse_lpeg.h Normal file
View File

@@ -0,0 +1,8 @@
#ifndef LPEG
#define LPEG
#define LPEGLIBNAME "lpeg"
LUALIB_API int luaopen_lpeg (lua_State *L);
#endif

View File

@@ -19,6 +19,7 @@
#include "nse_pcrelib.h" #include "nse_pcrelib.h"
#include "nse_openssl.h" #include "nse_openssl.h"
#include "nse_debug.h" #include "nse_debug.h"
#include "nse_lpeg.h"
#define NSE_MAIN "NSE_MAIN" /* the main function */ #define NSE_MAIN "NSE_MAIN" /* the main function */
@@ -543,6 +544,7 @@ static void set_nmap_libraries (lua_State *L)
{NSE_BINLIBNAME, luaopen_binlib}, {NSE_BINLIBNAME, luaopen_binlib},
{BITLIBNAME, luaopen_bit}, {BITLIBNAME, luaopen_bit},
{LFSLIBNAME, luaopen_lfs}, {LFSLIBNAME, luaopen_lfs},
{LPEGLIBNAME, luaopen_lpeg},
#ifdef HAVE_OPENSSL #ifdef HAVE_OPENSSL
{OPENSSLLIBNAME, luaopen_openssl}, {OPENSSLLIBNAME, luaopen_openssl},
#endif #endif

View File

@@ -115,6 +115,7 @@ local gsub = string.gsub;
local lower = string.lower; local lower = string.lower;
local match = string.match; local match = string.match;
local sub = string.sub; local sub = string.sub;
local upper = string.upper;
local table = require "table"; local table = require "table";
local concat = table.concat; local concat = table.concat;
@@ -137,6 +138,19 @@ do -- Add loader to look in nselib/?.lua (nselib/ can be in multiple places)
insert(package.searchers, 1, loader); insert(package.searchers, 1, loader);
end end
local lpeg = require "lpeg";
local locale = lpeg.locale;
local P = lpeg.P;
local R = lpeg.R;
local S = lpeg.S;
local V = lpeg.V;
local C = lpeg.C;
local Cb = lpeg.Cb;
local Cc = lpeg.Cc;
local Cf = lpeg.Cf;
local Cg = lpeg.Cg;
local Ct = lpeg.Ct;
local nmap = require "nmap"; local nmap = require "nmap";
local lfs = require "lfs"; local lfs = require "lfs";
@@ -256,6 +270,12 @@ local function host_copy(t)
return h return h
end end
-- Return a pattern which matches a "keyword" literal, case insensitive.
local function K (a)
local insensitize = Cf((P(1) / function (a) return S(lower(a)..upper(a)) end)^1, function (a, b) return a * b end);
return assert(insensitize:match(a)) * -(locale().alnum + P "_"); -- "keyword" token
end
local REQUIRE_ERROR = {}; local REQUIRE_ERROR = {};
rawset(stdnse, "silent_require", function (...) rawset(stdnse, "silent_require", function (...)
local status, mod = pcall(require, ...); local status, mod = pcall(require, ...);
@@ -639,14 +659,7 @@ local function get_chosen_scripts (rules)
"\tplease update using: nmap --script-updatedb"); "\tplease update using: nmap --script-updatedb");
local chosen_scripts, files_loaded = {}, {}; local chosen_scripts, files_loaded = {}, {};
local entry_rules, used_rules, forced_rules = {}, {}, {}; local used_rules, forced_rules = {}, {};
-- Tokens that are allowed in script rules (--script)
local protected_lua_tokens = {
["and"] = true,
["or"] = true,
["not"] = true,
};
-- Was this category selection forced to run (e.g. "+script"). -- Was this category selection forced to run (e.g. "+script").
-- Return: -- Return:
@@ -661,16 +674,6 @@ local function get_chosen_scripts (rules)
end end
end end
-- Globalize all names in str that are not protected_lua_tokens
local function globalize (str)
local lstr = lower(str);
if protected_lua_tokens[lstr] then
return lstr;
else
return 'm("'..str..'")';
end
end
for i, rule in ipairs(rules) do for i, rule in ipairs(rules) do
rule = match(rule, "^%s*(.-)%s*$"); -- strip surrounding whitespace rule = match(rule, "^%s*(.-)%s*$"); -- strip surrounding whitespace
local original_rule = rule; local original_rule = rule;
@@ -679,80 +682,60 @@ local function get_chosen_scripts (rules)
forced_rules[rule] = forced; forced_rules[rule] = forced;
-- Here we escape backslashes which might appear in Windows filenames. -- Here we escape backslashes which might appear in Windows filenames.
rule = gsub(rule, "\\([^\\])", "\\\\%1"); rule = gsub(rule, "\\([^\\])", "\\\\%1");
-- Globalize all `names`, all visible characters not ',', '(', ')', and ';' rules[i] = rule;
local globalized_rule =
gsub(rule, "[\033-\039\042-\043\045-\058\060-\126]+", globalize);
-- Precompile the globalized rule
local env = {m = nil};
local compiled_rule, err = load("return "..globalized_rule, "rule", "t", env);
if not compiled_rule then
err = err:match("rule\"]:%d+:(.+)$"); -- remove (luaL_)where in code
error("Bad script rule:\n\t"..original_rule.." -> "..err);
end
-- These are used to reference and check all the rules later.
entry_rules[globalized_rule] = {
original_rule = rule,
compiled_rule = compiled_rule,
env = env,
};
end end
-- Checks if a given script, script_entry, should be loaded. A script_entry -- Checks if a given script, script_entry, should be loaded. A script_entry
-- should be in the form: { filename = "name.nse", categories = { ... } } -- should be in the form: { filename = "name.nse", categories = { ... } }
function db_env.Entry (script_entry) function db_env.Entry (script_entry)
local categories, filename = script_entry.categories, script_entry.filename; local categories = rawget(script_entry, "categories");
assert(type(categories) == "table" and type(filename) == "string", local filename = rawget(script_entry, "filename");
"script database appears corrupt, try `nmap --script-updatedb`"); assert(type(categories) == "table" and type(filename) == "string", "script database appears corrupt, try `nmap --script-updatedb`");
local escaped_basename = match(filename, "([^/\\]-)%.nse$") or local escaped_basename = match(filename, "([^/\\]-)%.nse$") or match(filename, "([^/\\]-)$");
match(filename, "([^/\\]-)$"); local selected_by_name = false;
local r_categories = {all = true}; -- A reverse table of categories
for i, category in ipairs(categories) do
assert(type(category) == "string", "bad entry in script database");
r_categories[lower(category)] = true; -- Lowercase the entry
end
-- The script selection parameters table. -- The script selection parameters table.
local script_params = {}; local script_params = {};
-- A matching function for each script rule. -- Test if path is a glob pattern that matches script_entry.filename.
-- If the pattern directly matches a category (e.g. "all"), then local function match_script (path)
-- we return true. Otherwise we test if it is a filename or if path = gsub(path, "%.nse$", ""); -- remove optional extension
-- the script_entry.filename matches the pattern. path = gsub(path, "[%^%$%(%)%%%.%[%]%+%-%?]", "%%%1"); -- esc magic
local function m (pattern) path = gsub(path, "%*", ".*"); -- change to Lua wildcard
-- Check categories path = "^"..path.."$"; -- anchor to beginning and end
if r_categories[lower(pattern)] then local found = not not find(escaped_basename, path);
script_params.selection = "category"; selected_by_name = selected_by_name or found;
return true; return found;
end
-- Check filename with wildcards
pattern = gsub(pattern, "%.nse$", ""); -- remove optional extension
pattern = gsub(pattern, "[%^%$%(%)%%%.%[%]%+%-%?]", "%%%1"); -- esc magic
pattern = gsub(pattern, "%*", ".*"); -- change to Lua wildcard
pattern = "^"..pattern.."$"; -- anchor to beginning and end
if find(escaped_basename, pattern) then
script_params.selection = "name";
script_params.verbosity = true;
return true;
end
return false;
end end
for globalized_rule, rule_table in pairs(entry_rules) do local T = locale {
-- Clear and set the environment of the compiled script rule V "space"^0 * V "expression" * V "space"^0 * P(-1);
rule_table.env.m = m;
local status, found = pcall(rule_table.compiled_rule) expression = V "disjunct" + V "conjunct" + V "value";
rule_table.env.m = nil; disjunct = (V "conjunct" + V "value") * V "space"^0 * K "or" * V "space"^0 * V "expression" / function (a, b) return a or b end;
if not status then conjunct = V "value" * V "space"^0 * K "and" * V "space"^0 * V "expression" / function (a, b) return a and b end;
error("Bad script rule:\n\t"..rule_table.original_rule.. value = K "not" * V "space"^0 * V "value" / function (a) return not a end +
" -> script rule expression not supported."); P "(" * V "space"^0 * V "expression" * V "space"^0 * P ")" +
end K "true" * Cc(true) +
-- The script rule matches a category or a pattern K "false" * Cc(false) +
if found then V "category" +
used_rules[rule_table.original_rule] = true; V "path";
script_params.forced = not not forced_rules[rule_table.original_rule];
category = K "all" * Cc(true); -- pseudo-category "all" matches everything
path = R("\033\039", "\042\126")^1 / match_script; -- all graphical characters not '(', ')'
};
for i, category in ipairs(categories) do
assert(type(category) == "string", "bad entry in script database");
T.category = T.category + K(category) * Cc(true);
end
T = P(T);
for i, rule in ipairs(rules) do
selected_by_name = false;
if T:match(rule) then
used_rules[rule] = true;
script_params.forced = not not forced_rules[rule];
local t, path = cnse.fetchscript(filename); local t, path = cnse.fetchscript(filename);
if t == "file" then if t == "file" then
if not files_loaded[path] then if not files_loaded[path] then
@@ -1169,85 +1152,57 @@ local function script_help_xml(chosen_scripts)
cnse.xml_newline(); cnse.xml_newline();
end end
do -- Load script arguments (--script-args) nmap.registry.args = {};
local args = cnse.scriptargs or ""; do
print_debug(1, "Script Arguments seen from CLI: %s", args); local args = {};
-- Parse a string in 'str' at 'start'. if cnse.scriptargsfile then
local function parse_string (str, start)
-- Unquoted
local uqi, uqj, uqm = find(str,
"^%s*([^'\"%s{},=][^{},=]-)%s*[},=]", start);
-- Quoted
local qi, qj, q, qm = find(str, "^%s*(['\"])(.-[^\\])%1%s*[},=]", start);
-- Empty Quote
local eqi, eqj = find(str, "^%s*(['\"])%1%s*[},=]", start);
if uqi then
return uqm, uqj-1;
elseif qi then
return gsub(qm, "\\"..q, q), qj-1;
elseif eqi then
return "", eqj-1;
else
error("Value around '"..sub(str, start, start+10)..
"' is invalid or is unterminated by a valid separator");
end
end
-- Takes 'str' at index 'start' and parses a table.
-- Returns the table and the place in the string it finished reading.
local function parse_table (str, start)
local _, j = find(str, "^%s*{", start);
local t = {}; -- table we return
local tmp, nc; -- temporary and next character inspected
while true do
j = j+1; -- move past last token
_, j, nc = find(str, "^%s*(%S)", j);
if nc == "}" then -- end of table
return t, j;
else -- try to read key/value pair, or array value
local av = false; -- this is an array value?
if nc == "{" then -- array value
av, tmp, j = true, parse_table(str, j);
else
tmp, j = parse_string(str, j);
end
nc = sub(str, j+1, j+1); -- next token
if not av and nc == "=" then -- key/value?
_, j, nc = find(str, "^%s*(%S)", j+2);
if nc == "{" then
t[tmp], j = parse_table(str, j);
else -- regular string
t[tmp], j = parse_string(str, j);
end
nc = sub(str, j+1, j+1); -- next token
else -- not key/value pair, save array value
t[#t+1] = tmp;
end
if nc == "," then j = j+1 end -- skip "," token
end
end
end
nmap.registry.args = parse_table("{"..args.."}", 1);
-- Check if user wants to read scriptargs from a file
if cnse.scriptargsfile ~= nil then --scriptargsfile path/to/file
local t, path = cnse.fetchfile_absolute(cnse.scriptargsfile) local t, path = cnse.fetchfile_absolute(cnse.scriptargsfile)
assert(t == 'file', format("%s is not a file", path)) assert(t == 'file', format("%s is not a file", path))
local argfile = assert(open(path, 'r')); print_debug(1, "Loading script-args from file `%s'", cnse.scriptargsfile);
local argstring = argfile:read("*a") args[#args+1] = assert(assert(open(path, 'r')):read "*a"):gsub("\n", ","):gsub(",*$", "");
argstring = gsub(argstring,"\n",",")
local tmpargs = parse_table("{"..argstring.."}",1)
for k,v in pairs(nmap.registry.args) do
tmpargs[k] = v
end
nmap.registry.args = tmpargs
end end
if debugging() >= 2 then
local out = {} if cnse.scriptargs then -- Load script arguments (--script-args)
rawget(stdnse, "pretty_printer")(nmap.registry.args, function (s) out[#out+1] = s end) print_debug(1, "Arguments from CLI: %s", cnse.scriptargs);
print_debug(2, "%s", concat(out)) args[#args+1] = cnse.scriptargs;
end
args = concat(args, ",");
if #args > 0 then
print_debug(1, "Arguments parsed: %s", args);
local function set (t, a, b)
if b == nil then
insert(t, a);
return t;
else
return rawset(t, a, b);
end
end
local parser = locale {
V "space"^0 * V "table" * V "space"^0,
table = Cf(Ct "" * P "{" * V "space"^0 * (V "fieldlst")^-1 * V "space"^0 * P "}", set);
fieldlst = V "field" * (V "space"^0 * P "," * V "space"^0 * V "field")^0;
field = V "kv" + V "av";
kv = Cg(V "string" * V "space"^0 * P "=" * V "space"^0 * V "value");
av = Cg(V "value");
value = V "table" + V "string";
string = V "qstring" + V "uqstring";
qstring = P "'" * C((-P "'" * (P "\\'" + P(1)))^0) * P "'" +
P '"' * C((-P '"' * (P '\\"' + P(1)))^0) * P '"';
uqstring = V "space"^0 * C((P(1) - V "space"^0 * S ",}=")^0) * V "space"^0; -- everything but ',}=', do not capture final space
};
parser = assert(P(parser));
nmap.registry.args = parser:match("{"..args.."}");
if not nmap.registry.args then
log_write("stdout", "args = "..args);
error "arguments did not parse!"
end
if debugging() >= 2 then
local out = {}
rawget(stdnse, "pretty_printer")(nmap.registry.args, function (s) out[#out+1] = s end)
print_debug(2, "%s", concat(out))
end
end end
end end

View File

@@ -12,7 +12,7 @@
-- <code>undefined</code>.) <code>NULL</code> values in JSON are represented by -- <code>undefined</code>.) <code>NULL</code> values in JSON are represented by
-- the special value <code>json.NULL</code>. -- the special value <code>json.NULL</code>.
-- --
-- @author Martin Holst Swende -- @author Martin Holst Swende (originally), David Fifield, Patrick Donnelly
-- @copyright Same as Nmap--See http://nmap.org/book/man-legal.html -- @copyright Same as Nmap--See http://nmap.org/book/man-legal.html
-- TODO: Unescape/escape unicode -- TODO: Unescape/escape unicode
@@ -23,7 +23,7 @@
-- Modified 02/27/2010 - v0.4 Added unicode handling (written by David Fifield). Renamed toJson -- Modified 02/27/2010 - v0.4 Added unicode handling (written by David Fifield). Renamed toJson
-- and fromJson into generate() and parse(), implemented more proper numeric parsing and added some more error checking. -- and fromJson into generate() and parse(), implemented more proper numeric parsing and added some more error checking.
local bit = require "bit" local bit = require "bit";
local nmap = require "nmap" local nmap = require "nmap"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local string = require "string" local string = require "string"
@@ -31,6 +31,155 @@ local table = require "table"
local unicode = require "unicode" local unicode = require "unicode"
_ENV = stdnse.module("json", stdnse.seeall) _ENV = stdnse.module("json", stdnse.seeall)
local lpeg = require "lpeg";
local locale = lpeg.locale;
local P = lpeg.P;
local R = lpeg.R;
local S = lpeg.S;
local V = lpeg.V;
local C = lpeg.C;
local Cb = lpeg.Cb;
local Cc = lpeg.Cc;
local Cf = lpeg.Cf;
local Cg = lpeg.Cg;
local Cp = lpeg.Cp;
local Cs = lpeg.Cs;
local Ct = lpeg.Ct;
local Cmt = lpeg.Cmt;
-- case sensitive keyword
local function K (a)
return P(a) * -(locale().alnum + "_");
end
local NULL = {};
_M.NULL = NULL;
-- Encode a Unicode code point to UTF-8. See RFC 3629.
-- Does not check that cp is a real charaacter; that is, doesn't exclude the
-- surrogate range U+D800 - U+DFFF and a handful of others.
local function utf8_enc (cp)
local result = {};
local n, mask;
if cp % 1.0 ~= 0.0 or cp < 0 then
-- Only defined for nonnegative integers.
error("utf code point defined only for non-negative integers");
elseif cp <= 0x7F then
-- Special case of one-byte encoding.
return string.char(cp);
elseif cp <= 0x7FF then
n = 2;
mask = 0xC0;
elseif cp <= 0xFFFF then
n = 3;
mask = 0xE0;
elseif cp <= 0x10FFFF then
n = 4;
mask = 0xF0;
else
assert(false);
end
while n > 1 do
result[n] = 0x80 + bit.band(cp, 0x3F);
cp = bit.rshift(cp, 6);
n = n - 1;
end
result[1] = mask + cp;
return string.char(unpack(result));
end
-- Decode a Unicode escape, assuming that self.pos starts just after the
-- initial \u. May consume an additional escape in the case of a UTF-16
-- surrogate pair. See RFC 2781 for UTF-16.
local unicode = P [[\u]] * C(locale().xdigit * locale().xdigit * locale().xdigit * locale().xdigit);
local function unicode16 (subject, position, hex)
local cp = assert(tonumber(hex, 16));
if cp < 0xD800 or cp > 0xDFFF then
return position, utf8_enc(cp);
elseif cp >= 0xDC00 and cp <= 0xDFFF then
error(("Not a Unicode character: U+%04X"):format(cp));
end
-- Beginning of a UTF-16 surrogate.
local lowhex = unicode:match(subject, position);
if not lowhex then
error(("Bad unicode escape \\u%s (missing low surrogate)"):format(hex))
else
local cp2 = assert(tonumber(lowhex, 16));
if not (cp2 >= 0xDC00 and cp2 <= 0xDFFF) then
error(("Bad unicode escape \\u%s\\u%s (bad low surrogate)"):format(hex, lowhex))
end
position = position+4;
cp = 0x10000 + bit.band(cp, 0x3FF) * 0x400 + bit.band(cp2, 0x3FF)
return position, utf8_enc(cp);
end
end
-- call lpeg.locale on the grammar to add V "space"
local json = locale {
V "json";
json = V "space"^0 * V "value" * V "space"^0 * P(-1); -- FIXME should be 'V "object" + V "array"' instead of 'V "value"' ?
value = V "string" +
V "number" +
V "object" +
V "array" +
K "true" * Cc(true)+
K "false" * Cc(false)+
K "null" * Cc(NULL);
object = Cf(Ct "" * P "{" * V "space"^0 * (V "members")^-1 * V "space"^0 * P "}", rawset);
members = V "pair" * (V "space"^0 * P "," * V "space"^0 * V "pair")^0;
pair = Cg(V "string" * V "space"^0 * P ":" * V "space"^0 * V "value");
array = Ct(P "[" * V "space"^0 * (V "elements")^-1 * V "space"^0 * P "]");
elements = V "value" * V "space"^0 * (P "," * V "space"^0 * V "value")^0;
string = Ct(P [["]] * (V "char")^0 * P [["]]) / table.concat;
char = P [[\"]] * Cc [["]] +
P [[\\]] * Cc [[\]] +
P [[\b]] * Cc "\b" +
P [[\f]] * Cc "\f" +
P [[\n]] * Cc "\n" +
P [[\r]] * Cc "\r" +
P [[\t]] * Cc "\t" +
P [[\u]] * Cmt(C(V "xdigit" * V "xdigit" * V "xdigit" * V "xdigit"), unicode16) +
P [[\]] * C(1) +
(C(1) - P [["]]);
number = C((P "-")^-1 * V "space"^0 * (V "hexadecimal" + V "floating" + V "integer")) / function (a) return assert(tonumber(a)) end;
hexadecimal = P "0x" * V "xdigit"^1;
floating = (V "digit"^1 * P "." * V "digit"^0 + V "digit"^0 * P "." * V "digit"^1) * (V "exponent")^-1;
integer = V "digit"^1 * (V "exponent")^-1;
exponent = S "eE" * (S "-+")^-1 * V "digit"^1;
};
json = P(json); -- compile the grammar
--- Parses JSON data into a Lua object.
-- This is the method you probably want to use if you use this library from a
-- script.
--@param data a json string
--@return status true if ok, false if bad
--@return an object representing the json, or error message
function parse (data)
local status, object = pcall(json.match, json, data);
if not status then
return false, object;
elseif object then
return true, object;
else
return false, "syntax error";
end
end
--Some local shortcuts --Some local shortcuts
local function dbg(str,...) local function dbg(str,...)
stdnse.print_debug("Json:"..str, ...) stdnse.print_debug("Json:"..str, ...)
@@ -47,9 +196,6 @@ local function dbg_err(str,...)
stdnse.print_debug("json-ERR:"..str, ...) stdnse.print_debug("json-ERR:"..str, ...)
end end
-- Javascript null representation, see explanation above
NULL = {}
-- See section 2.5 for escapes. -- See section 2.5 for escapes.
-- For convenience, ESCAPE_TABLE maps to escape sequences complete with -- For convenience, ESCAPE_TABLE maps to escape sequences complete with
-- backslash, and REVERSE_ESCAPE_TABLE maps from single escape characters -- backslash, and REVERSE_ESCAPE_TABLE maps from single escape characters
@@ -125,7 +271,6 @@ end
--@param obj a table containing data --@param obj a table containing data
--@return a string containing valid json --@return a string containing valid json
function generate(obj) function generate(obj)
-- NULL-check must be performed before -- NULL-check must be performed before
-- checking type == table, since the NULL-object -- checking type == table, since the NULL-object
-- is a table -- is a table
@@ -158,302 +303,6 @@ function generate(obj)
error("Unknown data type in generate") error("Unknown data type in generate")
end end
-- This is the parser, implemented in OO-form to deal with state better
Json = {}
-- Constructor
function Json:new(input)
local o = {}
setmetatable(o, self)
self.__index = self
o.input = input
o.pos = 1 -- Pos is where the NEXT letter will be read
return o
end
-- Gets next character and ups the position
--@return next character
function Json:next()
self.pos = self.pos+1
return self.input:sub(self.pos-1, self.pos-1)
end
-- Updates the position to next non whitespace position
function Json:eatWhiteSpace()
--Find next non-white char
local a,b = self.input:find("%S",self.pos)
if not a then
self:syntaxerror("Empty data")
return
end
self.pos = a
end
-- Jumps to a specified position
--@param position where to go
function Json:jumpTo(position)
self.pos = position
end
-- Returns next character, but without upping position
--@return next character
function Json:peek()
return self.input:sub(self.pos, self.pos)
end
--@return true if more input is in store
function Json:hasMore()
return self.input:len() >= self.pos
end
-- Checks that the following input is equal to a string
-- and updates position so next char will be after that string
-- If false, triggers a syntax error
--@param str the string to test
function Json:assertStr(str)
local content = self.input:sub(self.pos,self.pos+str:len()-1)
if(content == str) then-- All ok
-- Jump forward
self:jumpTo(self.pos+str:len())
return
end
self:syntaxerror(("Expected '%s' but got '%s'"):format( str, content))
end
-- Trigger a syntax error
function Json:syntaxerror(reason)
self.error = ("Syntax error near pos %d: %s input: %s"):format( self.pos, reason, self.input)
dbg(self.error)
end
-- Check if any errors has occurred
function Json:errors()
return self.error ~= nil
end
-- Parses a top-level JSON structure (object or array).
--@return the parsed object or puts error messages in self.error
function Json:parseStart()
-- The top level of JSON only allows an object or an array. Only inside
-- of the outermost container can other types appear.
self:eatWhiteSpace()
local c = self:peek()
if c == '{' then
return self:parseObject()
elseif c == '[' then
return self:parseArray()
else
self:syntaxerror(("JSON must start with object or array (started with %s)"):format(c))
return
end
end
-- Parses a value
--@return the parsed value
function Json:parseValue()
self:eatWhiteSpace()
local c = self:peek()
local value
if c == '{' then
value = self:parseObject()
elseif c == '[' then
value = self:parseArray()
elseif c == '"' then
value = self:parseString()
elseif c == 'n' then
self:assertStr("null")
value = NULL
elseif c == 't' then
self:assertStr("true")
value = true
elseif c == 'f' then
self:assertStr("false")
value = false
else -- numeric
-- number = [ minus ] int [ frac ] [ exp ]
local a,b =self.input:find("-?%d+%.?%d*[eE]?[+-]?%d*", self.pos)
if not a or not b then
self:syntaxerror("Error 1 parsing numeric value")
return
end
value = tonumber(self.input:sub(a,b))
if(value == nil) then
self:syntaxerror("Error 2 parsing numeric value")
return
end
self:jumpTo(b+1)
end
return value
end
-- Parses a json object {}
--@return the object (or triggers a syntax error)
function Json:parseObject()
local object = {}
make_object(object)
local _= self:next() -- Eat {
while(self:hasMore() and not self:errors()) do
self:eatWhiteSpace()
local c = self:peek()
if(c == '}') then -- Empty object, probably
self:next() -- Eat it
return object
end
if(c ~= '"') then
self:syntaxerror(("Expected '\"', got '%s'"):format(c))
return
end
local key = self:parseString()
if self:errors() then
return
end
self:eatWhiteSpace()
c = self:next()
if(c ~= ':') then
self:syntaxerror("Expected ':' got "..c)
return
end
local value = self:parseValue()
if self:errors() then
return
end
object[key] = value
self:eatWhiteSpace()
c = self:next()
-- Valid now is , or }
if(c == '}') then
return object
end
if(c ~= ',') then
self:syntaxerror("Expected ',' or '}', got "..c)
return
end
end
end
-- Parses a json array [] or triggers a syntax error
--@return the array object
function Json:parseArray()
local array = {}
make_array(array)
self:next()
while(self:hasMore() and not self:errors()) do
self:eatWhiteSpace()
if(self:peek() == ']') then -- Empty array, probably
self:next()
break
end
local value = self:parseValue()
if self:errors() then
return
end
table.insert(array, value)
self:eatWhiteSpace()
local c = self:next()
-- Valid now is , or ]
if(c == ']') then return array end
if(c ~= ',') then
self:syntaxerror(("Expected ',' but got '%s'"):format(c))
return
end
end
return array
end
-- Decode a Unicode escape, assuming that self.pos starts just after the
-- initial \u. May consume an additional escape in the case of a UTF-16
-- surrogate pair. See RFC 2781 for UTF-16.
function Json:parseUnicodeEscape()
local n, cp
local hex, lowhex
local s, e
s, e, hex = self.input:find("^(....)", self.pos)
if not hex then
self:syntaxerror(("EOF in Unicode escape \\u%s"):format(self.input:sub(self.pos)))
return
end
n = tonumber(hex, 16)
if not n then
self:syntaxerror(("Bad unicode escape \\u%s"):format(hex))
return
end
cp = n
self.pos = e + 1
if n < 0xD800 or n > 0xDFFF then
return cp
end
if n >= 0xDC00 and n <= 0xDFFF then
self:syntaxerror(("Not a Unicode character: U+%04X"):format(cp))
return
end
-- Beginning of a UTF-16 surrogate.
s, e, lowhex = self.input:find("^\\u(....)", self.pos)
if not lowhex then
self:syntaxerror(("Bad unicode escape \\u%s (missing low surrogate)"):format(hex))
return
end
n = tonumber(lowhex, 16)
if not n or not (n >= 0xDC00 and n <= 0xDFFF) then
self:syntaxerror(("Bad unicode escape \\u%s\\u%s (bad low surrogate)"):format(hex, lowhex))
return
end
self.pos = e + 1
cp = 0x10000 + bit.band(cp, 0x3FF) * 0x400 + bit.band(n, 0x3FF)
-- also remove last "
return cp
end
-- Parses a json string
-- @return the string or triggers syntax error
function Json:parseString()
local val = ''
local c = self:next()
assert( c == '"')
while(self:hasMore()) do
local c = self:next()
if(c == '"') then -- end of string
break
elseif(c == '\\') then-- Escaped char
local d = self:next()
if REVERSE_ESCAPE_TABLE[d] ~= nil then
val = val .. REVERSE_ESCAPE_TABLE[d]
elseif d == 'u' then -- Unicode chars
local codepoint = self:parseUnicodeEscape()
if not codepoint then
return
end
val = val .. unicode.utf8_enc(codepoint)
else
self:syntaxerror(("Undefined escape character '%s'"):format(d))
return false
end
else -- Char
val = val .. c
end
end
return val
end
--- Parses json data into an object form
--
-- This is the method you probably want to use if you
-- use this library from a script.
--@param data a json string
--@return status true if ok, false if bad
--@return an object representing the json, or error message
function parse(data)
local parser = Json:new(data)
local result = parser:parseStart()
if(parser.error) then
return false, parser.error
end
return true, result
end
---------------------------------------------------------------------------------- ----------------------------------------------------------------------------------
-- Test-code for debugging purposes below -- Test-code for debugging purposes below
---------------------------------------------------------------------------------- ----------------------------------------------------------------------------------
@@ -470,10 +319,9 @@ local TESTS = {
'[1,2,3,4,5,null,false,true,"\195\164\195\165\195\182\195\177","bar"]', '[1,2,3,4,5,null,false,true,"\195\164\195\165\195\182\195\177","bar"]',
'[]',-- This will yield {} in toJson, since in lua there is only one basic datatype - and no difference when empty '[]',-- This will yield {} in toJson, since in lua there is only one basic datatype - and no difference when empty
'{}', '{}',
'', -- error
'', -- error 'null', -- error
'null', -- error '"abc"', -- error
'"abc"', -- error
'{a":1}', -- error '{a":1}', -- error
'{"a" bad :1}', -- error '{"a" bad :1}', -- error
'["a\\\\t"]', -- Should become Lua {"a\\t"} '["a\\\\t"]', -- Should become Lua {"a\\t"}
@@ -496,11 +344,11 @@ function test()
local i,v,res,status local i,v,res,status
for i,v in pairs(TESTS) do for i,v in pairs(TESTS) do
print("----------------------------") print("----------------------------")
print(v) print(("%q"):format(v))
status,res = parse(v) status,res = parse(v)
if not status then print( res) end if not status then print( res) end
if(status) then if(status) then
print(generate(res)) print(("%q"):format(generate(res)))
else else
print("Error:".. res) print("Error:".. res)
end end

72
nselib/lpeg/utility.lua Normal file
View File

@@ -0,0 +1,72 @@
---
-- Utility functions for LPeg.
--
-- @copyright Same as Nmap--See http://nmap.org/book/man-legal.html
-- @class module
-- @name lpeg.utility
local assert = assert
local lpeg = require "lpeg"
local stdnse = require "stdnse"
_ENV = {}
---
-- Returns a pattern which matches the literal string caselessly.
--
-- @param literal A literal string to match case-insensitively.
-- @return An LPeg pattern.
function caseless (literal)
local caseless = lpeg.Cf((lpeg.P(1) / function (a) return lpeg.S(a:lower()..a:upper()) end)^1, function (a, b) return a * b end)
return assert(caseless:match(literal))
end
---
-- Returns a pattern which matches the input pattern anywhere on a subject string.
--
-- @param patt Input pattern.
-- @return An LPeg pattern.
function anywhere (patt)
return lpeg.P {
patt + 1 * lpeg.V(1)
}
end
---
-- Adds the current locale from lpeg.locale() to the grammar and returns the final pattern.
--
-- @param grammar Input grammar.
-- @return An LPeg pattern.
function localize (grammar)
return lpeg.P(lpeg.locale(grammar))
end
---
-- Splits the input string on the input separator.
--
-- @param str Input string to split.
-- @param sep Input string/pattern to separate on.
-- @return All splits.
function split (str, sep)
return lpeg.P {
lpeg.V "elem" * (lpeg.V "sep" * lpeg.V "elem")^0,
elem = lpeg.C((1 - lpeg.V "sep")^0),
sep = sep,
} :match(str)
end
---
-- Returns a pattern which only matches at a word boundary (beginning).
--
-- Essentially the same as '\b' in a PCRE pattern.
--
-- @param patt A pattern.
-- @return A new LPeg pattern.
function atwordboundary (patt)
return _ENV.localize {
patt + lpeg.V "alpha"^0 * (1 - lpeg.V "alpha")^1 * lpeg.V(1)
}
end
return _ENV

View File

@@ -5,37 +5,16 @@
-- <code>nmap.receive_buf</code> function in the Network I/O API (which see). -- <code>nmap.receive_buf</code> function in the Network I/O API (which see).
-- @copyright Same as Nmap--See http://nmap.org/book/man-legal.html -- @copyright Same as Nmap--See http://nmap.org/book/man-legal.html
local pcre = require "pcre"
local stdnse = require "stdnse" local stdnse = require "stdnse"
_ENV = stdnse.module("match", stdnse.seeall) _ENV = stdnse.module("match", stdnse.seeall)
--various functions for use with NSE's nsock:receive_buf - function --various functions for use with NSE's nsock:receive_buf - function
-- e.g. -- e.g.
-- sock:receive_buf(regex("myregexpattern"), true) - does a match using pcre
-- regular expressions
-- sock:receive_buf(numbytes(80), true) - is the buffered version of -- sock:receive_buf(numbytes(80), true) - is the buffered version of
-- sock:receive_bytes(80) - i.e. it -- sock:receive_bytes(80) - i.e. it
-- returns exactly 80 bytes and no more -- returns exactly 80 bytes and no more
--- Return a function that allows delimiting with a regular expression.
--
-- This function is a wrapper around <code>pcre.exec</code>. Its purpose is to
-- give script developers the ability to use regular expressions for delimiting
-- instead of Lua's string patterns.
-- @param pattern The regex.
-- @usage sock:receive_buf(match.regex("myregexpattern"), true)
-- @see nmap.receive_buf
-- @see pcre.exec
regex = function(pattern)
local r = pcre.new(pattern, 0,"C")
return function(buf)
local s,e = r:exec(buf, 0,0);
return s,e
end
end
--- Return a function that allows delimiting at a certain number of bytes. --- Return a function that allows delimiting at a certain number of bytes.
-- --
-- This function can be used to get a buffered version of -- This function can be used to get a buffered version of

259
nselib/re.lua Normal file
View File

@@ -0,0 +1,259 @@
-- $Id: re.lua,v 1.44 2013/03/26 20:11:40 roberto Exp $
-- imported functions and modules
local tonumber, type, print, error = tonumber, type, print, error
local setmetatable = setmetatable
local m = require"lpeg"
-- 'm' will be used to parse expressions, and 'mm' will be used to
-- create expressions; that is, 're' runs on 'm', creating patterns
-- on 'mm'
local mm = m
-- pattern's metatable
local mt = getmetatable(mm.P(0))
-- No more global accesses after this point
local version = _VERSION
if version == "Lua 5.2" then _ENV = nil end
local any = m.P(1)
-- Pre-defined names
local Predef = { nl = m.P"\n" }
local mem
local fmem
local gmem
local function updatelocale ()
mm.locale(Predef)
Predef.a = Predef.alpha
Predef.c = Predef.cntrl
Predef.d = Predef.digit
Predef.g = Predef.graph
Predef.l = Predef.lower
Predef.p = Predef.punct
Predef.s = Predef.space
Predef.u = Predef.upper
Predef.w = Predef.alnum
Predef.x = Predef.xdigit
Predef.A = any - Predef.a
Predef.C = any - Predef.c
Predef.D = any - Predef.d
Predef.G = any - Predef.g
Predef.L = any - Predef.l
Predef.P = any - Predef.p
Predef.S = any - Predef.s
Predef.U = any - Predef.u
Predef.W = any - Predef.w
Predef.X = any - Predef.x
mem = {} -- restart memoization
fmem = {}
gmem = {}
local mt = {__mode = "v"}
setmetatable(mem, mt)
setmetatable(fmem, mt)
setmetatable(gmem, mt)
end
updatelocale()
local I = m.P(function (s,i) print(i, s:sub(1, i-1)); return i end)
local function getdef (id, defs)
local c = defs and defs[id]
if not c then error("undefined name: " .. id) end
return c
end
local function patt_error (s, i)
local msg = (#s < i + 20) and s:sub(i)
or s:sub(i,i+20) .. "..."
msg = ("pattern error near '%s'"):format(msg)
error(msg, 2)
end
local function mult (p, n)
local np = mm.P(true)
while n >= 1 do
if n%2 >= 1 then np = np * p end
p = p * p
n = n/2
end
return np
end
local function equalcap (s, i, c)
if type(c) ~= "string" then return nil end
local e = #c + i
if s:sub(i, e - 1) == c then return e else return nil end
end
local S = (Predef.space + "--" * (any - Predef.nl)^0)^0
local name = m.R("AZ", "az", "__") * m.R("AZ", "az", "__", "09")^0
local arrow = S * "<-"
local seq_follow = m.P"/" + ")" + "}" + ":}" + "~}" + "|}" + (name * arrow) + -1
name = m.C(name)
-- a defined name only have meaning in a given environment
local Def = name * m.Carg(1)
local num = m.C(m.R"09"^1) * S / tonumber
local String = "'" * m.C((any - "'")^0) * "'" +
'"' * m.C((any - '"')^0) * '"'
local defined = "%" * Def / function (c,Defs)
local cat = Defs and Defs[c] or Predef[c]
if not cat then error ("name '" .. c .. "' undefined") end
return cat
end
local Range = m.Cs(any * (m.P"-"/"") * (any - "]")) / mm.R
local item = defined + Range + m.C(any)
local Class =
"["
* (m.C(m.P"^"^-1)) -- optional complement symbol
* m.Cf(item * (item - "]")^0, mt.__add) /
function (c, p) return c == "^" and any - p or p end
* "]"
local function adddef (t, k, exp)
if t[k] then
error("'"..k.."' already defined as a rule")
else
t[k] = exp
end
return t
end
local function firstdef (n, r) return adddef({n}, n, r) end
local function NT (n, b)
if not b then
error("rule '"..n.."' used outside a grammar")
else return mm.V(n)
end
end
local exp = m.P{ "Exp",
Exp = S * ( m.V"Grammar"
+ m.Cf(m.V"Seq" * ("/" * S * m.V"Seq")^0, mt.__add) );
Seq = m.Cf(m.Cc(m.P"") * m.V"Prefix"^0 , mt.__mul)
* (#seq_follow + patt_error);
Prefix = "&" * S * m.V"Prefix" / mt.__len
+ "!" * S * m.V"Prefix" / mt.__unm
+ m.V"Suffix";
Suffix = m.Cf(m.V"Primary" * S *
( ( m.P"+" * m.Cc(1, mt.__pow)
+ m.P"*" * m.Cc(0, mt.__pow)
+ m.P"?" * m.Cc(-1, mt.__pow)
+ "^" * ( m.Cg(num * m.Cc(mult))
+ m.Cg(m.C(m.S"+-" * m.R"09"^1) * m.Cc(mt.__pow))
)
+ "->" * S * ( m.Cg((String + num) * m.Cc(mt.__div))
+ m.P"{}" * m.Cc(nil, m.Ct)
+ m.Cg(Def / getdef * m.Cc(mt.__div))
)
+ "=>" * S * m.Cg(Def / getdef * m.Cc(m.Cmt))
) * S
)^0, function (a,b,f) return f(a,b) end );
Primary = "(" * m.V"Exp" * ")"
+ String / mm.P
+ Class
+ defined
+ "{:" * (name * ":" + m.Cc(nil)) * m.V"Exp" * ":}" /
function (n, p) return mm.Cg(p, n) end
+ "=" * name / function (n) return mm.Cmt(mm.Cb(n), equalcap) end
+ m.P"{}" / mm.Cp
+ "{~" * m.V"Exp" * "~}" / mm.Cs
+ "{|" * m.V"Exp" * "|}" / mm.Ct
+ "{" * m.V"Exp" * "}" / mm.C
+ m.P"." * m.Cc(any)
+ (name * -arrow + "<" * name * ">") * m.Cb("G") / NT;
Definition = name * arrow * m.V"Exp";
Grammar = m.Cg(m.Cc(true), "G") *
m.Cf(m.V"Definition" / firstdef * m.Cg(m.V"Definition")^0,
adddef) / mm.P
}
local pattern = S * m.Cg(m.Cc(false), "G") * exp / mm.P * (-any + patt_error)
local function compile (p, defs)
if mm.type(p) == "pattern" then return p end -- already compiled
local cp = pattern:match(p, 1, defs)
if not cp then error("incorrect pattern", 3) end
return cp
end
local function match (s, p, i)
local cp = mem[p]
if not cp then
cp = compile(p)
mem[p] = cp
end
return cp:match(s, i or 1)
end
local function find (s, p, i)
local cp = fmem[p]
if not cp then
cp = compile(p) / 0
cp = mm.P{ mm.Cp() * cp * mm.Cp() + 1 * mm.V(1) }
fmem[p] = cp
end
local i, e = cp:match(s, i or 1)
if i then return i, e - 1
else return i
end
end
local function gsub (s, p, rep)
local g = gmem[p] or {} -- ensure gmem[p] is not collected while here
gmem[p] = g
local cp = g[rep]
if not cp then
cp = compile(p)
cp = mm.Cs((cp / rep + 1)^0)
g[rep] = cp
end
return cp:match(s)
end
-- exported names
local re = {
compile = compile,
match = match,
find = find,
gsub = gsub,
updatelocale = updatelocale,
}
if version == "Lua 5.1" then _G.re = re end
return re

View File

@@ -1,6 +1,6 @@
local http = require "http" local http = require "http"
local nmap = require "nmap" local nmap = require "nmap"
local pcre = require "pcre" local re = require "re"
local shortport = require "shortport" local shortport = require "shortport"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local table = require "table" local table = require "table"
@@ -42,7 +42,7 @@ Supported IDs:
-- | thisisphotobomb.memebase.com:80/ -- | thisisphotobomb.memebase.com:80/
-- |_ memebase.com:80/ -- |_ memebase.com:80/
author = "Hani Benhabiles, Daniel Miller" author = "Hani Benhabiles, Daniel Miller, Patrick Donnelly"
license = "Same as Nmap--See http://nmap.org/book/man-legal.html" license = "Same as Nmap--See http://nmap.org/book/man-legal.html"
@@ -51,9 +51,13 @@ categories = {"safe", "discovery"}
-- these are the regular expressions for affiliate IDs -- these are the regular expressions for affiliate IDs
local AFFILIATE_PATTERNS = { local AFFILIATE_PATTERNS = {
["Google Analytics ID"] = "(?P<id>UA-[0-9]{6,9}-[0-9]{1,2})", ["Google Analytics ID"] = re.compile [[{| ({'UA-' [%d]^6 [%d]^-3 '-' [%d][%d]?} / .)* |}]],
["Google Adsense ID"] = "(?P<id>pub-[0-9]{16,16})", ["Google Adsense ID"] = re.compile [[{| ({'pub-' [%d]^16} / .)* |}]],
["Amazon Associates ID"] = "http://(www%.amazon%.com/[^\"']*[\\?&;]tag|rcm%.amazon%.com/[^\"']*[\\?&;]t)=(?P<id>\\w+-\\d+)", ["Amazon Associates ID"] = re.compile [[
body <- {| (uri / .)* |}
uri <- 'http://' ('www.amazon.com/' ([\?&;] 'tag=' tag / [^"'])*) / ('rcm.amazon.com/' ([\?&;] 't=' tag / [^"'])*)
tag <- {[%w]+ '-' [%d]+}
]],
} }
portrule = shortport.http portrule = shortport.http
@@ -83,13 +87,14 @@ portaction = function(host, port)
end end
-- Here goes affiliate matching -- Here goes affiliate matching
for name, re in pairs(AFFILIATE_PATTERNS) do for name, pattern in pairs(AFFILIATE_PATTERNS) do
local regex = pcre.new(re, 0, "C") local ids = {}
local limit, limit2, matches = regex:match(body) for i, id in ipairs(pattern:match(body)) do
if limit ~= nil then if not ids[id] then
local affiliateid = matches["id"] result[#result + 1] = name .. ": " .. id
result[#result + 1] = name .. ": " .. affiliateid add_key_to_registry(host, port, url_path, result[#result])
add_key_to_registry(host, port, url_path, result[#result]) ids[id] = true
end
end end
end end

View File

@@ -1,7 +1,6 @@
local http = require "http" local http = require "http"
local io = require "io" local io = require "io"
local nmap = require "nmap" local nmap = require "nmap"
local pcre = require "pcre"
local shortport = require "shortport" local shortport = require "shortport"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local string = require "string" local string = require "string"
@@ -68,14 +67,8 @@ local get_modules_path = function(host, port, root)
local modules_path = stdnse.get_script_args(SCRIPT_NAME .. '.modules_path') local modules_path = stdnse.get_script_args(SCRIPT_NAME .. '.modules_path')
if modules_path == nil then if modules_path == nil then
-- greps response body for sign of the modules path
local pathregex = "sites/[a-zA-Z0-9.-]*/modules/"
local body = http.get(host, port, root).body local body = http.get(host, port, root).body
local regex = pcre.new(pathregex, 0, "C") modules_path = body:match "sites/[%w.-]*/modules/"
local limit, limit2, matches = regex:match(body)
if limit ~= nil then
modules_path = body:sub(limit, limit2)
end
end end
return modules_path or default_path return modules_path or default_path
end end

View File

@@ -1,6 +1,5 @@
local http = require "http" local http = require "http"
local nmap = require "nmap" local nmap = require "nmap"
local pcre = require "pcre"
local shortport = require "shortport" local shortport = require "shortport"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local table = require "table" local table = require "table"
@@ -69,29 +68,15 @@ portrule = shortport.service("http")
--- Attempts to extract the html title --- Attempts to extract the html title
-- from an HTTP response body. -- from an HTTP response body.
--@param responsebody Response's body. --@param responsebody Response's body.
local extract_title = function(responsebody) local function extract_title (responsebody)
local title = '' return responsebody:match "<title>(.-)</title>"
local titlere = '<title>(?P<title>.*)</title>'
local regex = pcre.new(titlere, 0, "C")
local limit, limit2, matches = regex:match(responsebody)
if limit ~= nil then
title = matches["title"]
end
return title
end end
--- Attempts to extract the X-Forwarded-For header --- Attempts to extract the X-Forwarded-For header
-- from an HTTP response body in case of TRACE requests. -- from an HTTP response body in case of TRACE requests.
--@param responsebody Response's body. --@param responsebody Response's body.
local extract_xfwd = function(responsebody) local function extract_xfwd (responsebody)
local xfwd = '' return responsebody:match "X-Forwarded-For: [^\r\n]*"
local xfwdre = '(?P<xfwd>X-Forwarded-For: .*)'
local regex = pcre.new(xfwdre, 0, "C")
local limit, limit2, matches = regex:match(responsebody)
if limit ~= nil then
xfwd = matches["xfwd"]
end
return xfwd
end end
--- Check for differences in response headers, status code --- Check for differences in response headers, status code

View File

@@ -1,7 +1,6 @@
local comm = require "comm" local comm = require "comm"
local math = require "math" local math = require "math"
local nmap = require "nmap" local nmap = require "nmap"
local pcre = require "pcre"
local shortport = require "shortport" local shortport = require "shortport"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local string = require "string" local string = require "string"
@@ -40,213 +39,144 @@ It uses STATS, LUSERS, and other queries to obtain this information.
-- <elem key="source host">source.example.com</elem> -- <elem key="source host">source.example.com</elem>
-- <elem key="source ident">NONE or BLOCKED</elem> -- <elem key="source ident">NONE or BLOCKED</elem>
author = "Doug Hoyte, Patrick Donnelly"
author = "Doug Hoyte"
license = "Same as Nmap--See http://nmap.org/book/man-legal.html" license = "Same as Nmap--See http://nmap.org/book/man-legal.html"
categories = {"default", "discovery", "safe"} categories = {"default", "discovery", "safe"}
portrule = shortport.port_or_service({6666,6667,6697,6679},{"irc","ircs"}) portrule = shortport.port_or_service({6666,6667,6697,6679},{"irc","ircs"})
local init = function() local banner_timeout = 60
-- Start of MOTD, we'll take the server name from here
nmap.registry.ircserverinfo_375 = nmap.registry.ircserverinfo_375
or pcre.new("^:([\\w-_.]+) 375", 0, "C")
-- MOTD could be missing, we want to handle that scenario as well local function random_nick ()
nmap.registry.ircserverinfo_422 = nmap.registry.ircserverinfo_422 local t = {}
or pcre.new("^:([\\w-_.]+) 422", 0, "C") for i = 1, 9 do -- minimum 9 char nick
t[i] = math.random(97, 122) -- lowercase ascii
-- NICK already in use end
nmap.registry.ircserverinfo_433 = nmap.registry.ircserverinfo_433 return ("%c"):rep(#t):format(table.unpack(t))
or pcre.new("^:[\\w-_.]+ 433", 0, "C")
-- PING/PONG
nmap.registry.ircserverinfo_ping = nmap.registry.ircserverinfo_ping
or pcre.new("^PING :(.+)", 0, "C")
-- Server version info
nmap.registry.ircserverinfo_351 = nmap.registry.ircserverinfo_351
or pcre.new("^:[\\w-_.]+ 351 \\w+ ([^:]+)", 0, "C")
-- Various bits of info
nmap.registry.ircserverinfo_251_efnet = nmap.registry.ircserverinfo_251_efnet
or pcre.new("^:[\\w-_.]+ 251 \\w+ :There are (\\d+) users and (\\d+) invisible on (\\d+) servers", 0, "C")
nmap.registry.ircserverinfo_251_ircnet = nmap.registry.ircserverinfo_251_ircnet
or pcre.new("^:[\\w-_.]+ 251 \\w+ :There are (\\d+) users and \\d+ services on (\\d+) servers", 0, "C")
nmap.registry.ircserverinfo_252 = nmap.registry.ircserverinfo_252
or pcre.new("^:[\\w-_.]+ 252 \\w+ (\\d+) :", 0, "C")
nmap.registry.ircserverinfo_254 = nmap.registry.ircserverinfo_254
or pcre.new("^:[\\w-_.]+ 254 \\w+ (\\d+) :", 0, "C")
nmap.registry.ircserverinfo_255_efnet = nmap.registry.ircserverinfo_255_efnet
or pcre.new("^:[\\w-_.]+ 255 \\w+ :I have (\\d+) clients and (\\d+) server", 0, "C")
nmap.registry.ircserverinfo_255_ircnet = nmap.registry.ircserverinfo_255_ircnet
or pcre.new("^:[\\w-_.]+ 255 \\w+ :I have (\\d+) users, \\d+ services and (\\d+) server", 0, "C")
nmap.registry.ircserverinfo_242 = nmap.registry.ircserverinfo_242
or pcre.new("^:[\\w-_.]+ 242 \\w+ :Server Up (\\d+ days, [\\d:]+)", 0, "C")
nmap.registry.ircserverinfo_352 = nmap.registry.ircserverinfo_352
or pcre.new("^:[\\w-_.]+ 352 \\w+ \\S+ (\\S+) ([\\w-_.]+)", 0, "C")
nmap.registry.ircserverinfo_error = nmap.registry.ircserverinfo_error
or pcre.new("^ERROR :(.*)", 0, "C")
end end
action = function(host, port) function action (host, port)
local sd = nmap.new_socket() local sd = nmap.new_socket()
local curr_nick = random_nick() local nick = random_nick()
local sver, shost, susers, sservers, schans, sircops, slusers, slservers, sup, serr
local myhost, myident
local s, e, t
local buf
local banner_timeout = 60
local make_output = function()
local o = stdnse.output_table()
if (not shost) then
if serr then
return "ERROR: " .. serr .. "\n"
else
return nil
end
end
o["server"] = shost local output = stdnse.output_table()
o["version"] = sver
o["servers"] = sservers
o["ops"] = sircops
o["chans"] = schans
o["users"] = susers
o["lservers"] = slservers
o["lusers"] = slusers
o["uptime"] = sup
o["source host"] = myhost
if myident and string.find(myident, "^~") then
o["source ident"] = "NONE or BLOCKED"
else
o["source ident"] = myident
end
return o local sd, line = comm.tryssl(host, port, "USER nmap +iw nmap :Nmap Wuz Here\nNICK " .. nick .. "\n")
end
init()
local sd, line = comm.tryssl(host, port, "USER nmap +iw nmap :Nmap Wuz Here\nNICK " .. curr_nick .. "\n")
if not sd then return "Unable to open connection" end if not sd then return "Unable to open connection" end
-- set a healthy banner timeout -- set a healthy banner timeout
sd:set_timeout(banner_timeout * 1000) sd:set_timeout(banner_timeout * 1000)
buf = stdnse.make_buffer(sd, "\r?\n") local buf = stdnse.make_buffer(sd, "\r?\n")
while true do while line do
if (not line) then break end stdnse.print_debug(2, "%s", line)
-- This one lets us know we've connected, pre-PONGed, and got a NICK -- This one lets us know we've connected, pre-PONGed, and got a NICK
s, e, t = nmap.registry.ircserverinfo_375:exec(line, 0, 0) -- Start of MOTD, we'll take the server name from here
if (s) then local info = line:match "^:([%w-_.]+) 375"
shost = string.sub(line, t[1], t[2]) if info then
sd:send("LUSERS\nVERSION\nSTATS u\nWHO " .. curr_nick .. "\nQUIT\n") output.server = info
sd:send("LUSERS\nVERSION\nSTATS u\nWHO " .. nick .. "\nQUIT\n")
end end
s, e, t = nmap.registry.ircserverinfo_422:exec(line, 0, 0) -- MOTD could be missing, we want to handle that scenario as well
if (s) then info = line:match "^:([%w-_.]+) 422"
shost = string.sub(line, t[1], t[2]) if info then
sd:send("LUSERS\nVERSION\nSTATS u\nWHO " .. curr_nick .. "\nQUIT\n") output.server = info
sd:send("LUSERS\nVERSION\nSTATS u\nWHO " .. nick .. "\nQUIT\n")
end end
s, e, t = nmap.registry.ircserverinfo_433:exec(line, 0, 0) -- NICK already in use
if (s) then info = line:match "^:([%w-_.]+) 433"
curr_nick = random_nick() if info then
sd:send("NICK " .. curr_nick .. "\n") nick = random_nick()
sd:send("NICK " .. nick .. "\n")
end end
s, e, t = nmap.registry.ircserverinfo_ping:exec(line, 0, 0) info = line:match "^:([%w-_.]+) 433"
if (s) then if info then
sd:send("PONG :" .. string.sub(line, t[1], t[2]) .. "\n") nick = random_nick()
sd:send("NICK " .. nick .. "\n")
end end
s, e, t = nmap.registry.ircserverinfo_351:exec(line, 0, 0) -- PING/PONG
if (s) then local dummy = line:match "^PING :(.*)"
sver = string.sub(line, t[1], t[2]) if dummy then
sd:send("PONG :" .. dummy .. "\n")
end end
s, e, t = nmap.registry.ircserverinfo_251_efnet:exec(line, 0, 0) -- Server version info
if (s) then info = line:match "^:[%w-_.]+ 351 %w+ ([^:]+)"
susers = (string.sub(line, t[1], t[2]) + string.sub(line, t[3], t[4])) if info then
sservers = string.sub(line, t[5], t[6]) output.version = info
end end
s, e, t = nmap.registry.ircserverinfo_251_ircnet:exec(line, 0, 0) -- Various bits of info
if (s) then local users, invisible, servers = line:match "^:[%w-_.]+ 251 %w+ :There are (%d+) users and (%d+) invisible on (%d+) servers"
susers = string.sub(line, t[1], t[2]) if users then
sservers = string.sub(line, t[3], t[4]) output.users = users + invisible
output.servers = servers
end end
s, e, t = nmap.registry.ircserverinfo_252:exec(line, 0, 0) local users, servers = line:match "^:[%w-_.]+ 251 %w+ :There are (%d+) users and %d+ services on (%d+) servers"
if (s) then if users then
sircops = string.sub(line, t[1], t[2]) output.users = users
output.servers = servers
end end
s, e, t = nmap.registry.ircserverinfo_254:exec(line, 0, 0) info = line:match "^:[%w-_.]+ 252 %w+ (%d+) :"
if (s) then if info then
schans = string.sub(line, t[1], t[2]) output.ops = info
end end
s, e, t = nmap.registry.ircserverinfo_255_efnet:exec(line, 0, 0) info = line:match "^:[%w-_.]+ 254 %w+ (%d+) :"
if (s) then if info then
slusers = string.sub(line, t[1], t[2]) output.chans = info
slservers = string.sub(line, t[3], t[4])
end end
s, e, t = nmap.registry.ircserverinfo_255_ircnet:exec(line, 0, 0) -- efnet
if (s) then local clients, servers = line:match "^:[%w-_.]+ 255 %w+ :I have (%d+) clients and (%d+) server"
slusers = string.sub(line, t[1], t[2]) if clients then
slservers = string.sub(line, t[3], t[4]) output.lusers = clients
output.lservers = servers
end end
s, e, t = nmap.registry.ircserverinfo_242:exec(line, 0, 0) -- ircnet
if (s) then local clients, servers = line:match "^:[%w-_.]+ 255 %w+ :I have (%d+) users, %d+ services and (%d+) server"
sup = string.sub(line, t[1], t[2]) if clients then
output.lusers = clients
output.lservers = servers
end end
s, e, t = nmap.registry.ircserverinfo_352:exec(line, 0, 0) local uptime = line:match "^:[%w-_.]+ 242 %w+ :Server Up (%d+ days, [%d:]+)"
if (s) then if uptime then
myident = string.sub(line, t[1], t[2]) output.uptime = uptime
myhost = string.sub(line, t[3], t[4])
end end
s, e, t = nmap.registry.ircserverinfo_error:exec(line, 0, 0) local ident, host = line:match "^:[%w-_.]+ 352 %w+ %S+ (%S+) ([%w-_.]+)"
if (s) then if ident then
serr = string.sub(line, t[1], t[2]) if ident:find "^~" then
return make_output() output["source ident"] = "NONE or BLOCKED"
else
output["source ident"] = ident
end
output["source host"] = host
end
local err = line:match "^ERROR :(.*)"
if err then
output.error = err
end end
line = buf() line = buf()
end end
return make_output() if output.server then
return output
end else
return nil
random_nick = function()
local nick = ""
-- NICKLEN is at least 9
for i = 0, 8, 1 do
nick = nick .. string.char(math.random(97, 122)) -- lowercase ascii
end end
return nick
end end

View File

@@ -1,12 +1,24 @@
local comm = require "comm" local comm = require "comm"
local coroutine = require "coroutine" local coroutine = require "coroutine"
local nmap = require "nmap" local nmap = require "nmap"
local re = require "re"
local U = require "lpeg.utility"
local shortport = require "shortport" local shortport = require "shortport"
local stdnse = require "stdnse" local stdnse = require "stdnse"
local strbuf = require "strbuf" local strbuf = require "strbuf"
local string = require "string" local string = require "string"
local brute = require "brute" local brute = require "brute"
local pcre = require "pcre"
local P = lpeg.P;
local R = lpeg.R;
local S = lpeg.S;
local V = lpeg.V;
local C = lpeg.C;
local Cb = lpeg.Cb;
local Cc = lpeg.Cc;
local Cf = lpeg.Cf;
local Cg = lpeg.Cg;
local Ct = lpeg.Ct;
description = [[ description = [[
Performs brute-force password auditing against telnet servers. Performs brute-force password auditing against telnet servers.
@@ -32,7 +44,7 @@ Performs brute-force password auditing against telnet servers.
-- count based on the behavior of the target -- count based on the behavior of the target
-- (default: "true") -- (default: "true")
author = "nnposter" author = "nnposter, Patrick Donnelly"
license = "Same as Nmap--See http://nmap.org/book/man-legal.html" license = "Same as Nmap--See http://nmap.org/book/man-legal.html"
categories = {'brute', 'intrusive'} categories = {'brute', 'intrusive'}
@@ -52,9 +64,6 @@ local login_debug = 2 -- debug level for printing attempted credentials
local detail_debug = 3 -- debug level for printing individual login steps local detail_debug = 3 -- debug level for printing individual login steps
-- and thread-level info -- and thread-level info
local pcreptn = {} -- cache of compiled PCRE patterns
--- ---
-- Print debug messages, prepending them with the script name -- Print debug messages, prepending them with the script name
-- --
@@ -65,6 +74,20 @@ local print_debug = function (level, fmt, ...)
stdnse.print_debug(level, "%s: " .. fmt, SCRIPT_NAME, ...) stdnse.print_debug(level, "%s: " .. fmt, SCRIPT_NAME, ...)
end end
local patt_login = U.atwordboundary(re.compile [[([uU][sS][eE][rR][nN][aA][mM][eE] / [lL][oO][gG][iI][nN]) %s* ':' %s* !.]])
local patt_password = U.atwordboundary(re.compile [[[pP][aA][sS][sS] ([wW][oO][rR][dD] / [cC][oO][dD][eE]) %s* ':' %s* !.]])
local patt_login_success = re.compile([[
prompt <- [/>%$#] \ -- general prompt
[lL][aA][sS][tT] %s+ [lL][oO][gG][iI][nN] %s* ':' \ -- linux telnetd
[A-Z] ':\\' \ -- Windows telnet
'Main' (%s \ %ESC '[' %d+ ';' %d+ 'H') 'Menu' \ -- Netgear RM356
[mM][aA][iI][nN] (%s \ '\x1B' ) [mM][eE][nN][uU] ! %a \ -- Netgear RM356
[eE][nN][tT][eE][rR] %s+ [tT][eE][rR][mM][iI][nN][aA][lL] %s+ [eE][mM][uU][lL][aA][tT][iI][oO][nN] %s* ':' -- Hummingbird telnetd
]], {ESC = "\x1B"})
local patt_login_failure = U.atwordboundary(U.caseless "incorrect" + U.caseless "failed" + U.caseless "denied" + U.caseless "invalid" + U.caseless "bad")
--- ---
-- Decide whether a given string (presumably received from a telnet server) -- Decide whether a given string (presumably received from a telnet server)
@@ -73,10 +96,7 @@ end
-- @param str The string to analyze -- @param str The string to analyze
-- @return Verdict (true or false) -- @return Verdict (true or false)
local is_username_prompt = function (str) local is_username_prompt = function (str)
pcreptn.username_prompt = pcreptn.username_prompt return not not login_patt:match(str)
or pcre.new("\\b(?:username|login)\\s*:\\s*$",
pcre.flags().CASELESS, "C")
return pcreptn.username_prompt:match(str)
end end
@@ -87,10 +107,7 @@ end
-- @param str The string to analyze -- @param str The string to analyze
-- @return Verdict (true or false) -- @return Verdict (true or false)
local is_password_prompt = function (str) local is_password_prompt = function (str)
pcreptn.password_prompt = pcreptn.password_prompt return not not password_patt:match(str)
or pcre.new("\\bpass(?:word|code)\\s*:\\s*$",
pcre.flags().CASELESS, "C")
return pcreptn.password_prompt:match(str)
end end
@@ -101,14 +118,7 @@ end
-- @param str The string to analyze -- @param str The string to analyze
-- @return Verdict (true or false) -- @return Verdict (true or false)
local is_login_success = function (str) local is_login_success = function (str)
pcreptn.login_success = pcreptn.login_success return not not password_login_success:match(str)
or pcre.new("[/>%$#]\\s*$" -- general prompt
.. "|^Last login\\s*:" -- linux telnetd
.. "|^(?-i:[A-Z]):\\\\" -- Windows telnet
.. "|Main(?:\\s|\\x1B\\[\\d+;\\d+H)Menu\\b" -- Netgear RM356
.. "|^Enter Terminal Emulation:\\s*$", -- Hummingbird telnetd
pcre.flags().CASELESS, "C")
return pcreptn.login_success:match(str)
end end
@@ -119,10 +129,7 @@ end
-- @param str The string to analyze -- @param str The string to analyze
-- @return Verdict (true or false) -- @return Verdict (true or false)
local is_login_failure = function (str) local is_login_failure = function (str)
pcreptn.login_failure = pcreptn.login_failure return not not patt_login_failure:match(str)
or pcre.new("\\b(?:incorrect|failed|denied|invalid|bad)\\b",
pcre.flags().CASELESS, "C")
return pcreptn.login_failure:match(str)
end end