From 601ad8d59f11d7180015d0ecfb9d0a8d67f6f5c1 Mon Sep 17 00:00:00 2001 From: Thijs Schreijer <thijs@thijsschreijer.nl> Date: Fri, 18 Mar 2022 12:12:39 +0100 Subject: refactor: Address issues raised by linter --- etc/cookie.lua | 22 +++++++++++----------- etc/get.lua | 2 +- 2 files changed, 12 insertions(+), 12 deletions(-) (limited to 'etc') diff --git a/etc/cookie.lua b/etc/cookie.lua index 4adb403..fec10a1 100644 --- a/etc/cookie.lua +++ b/etc/cookie.lua @@ -5,7 +5,7 @@ local ltn12 = require"ltn12" local token_class = '[^%c%s%(%)%<%>%@%,%;%:%\\%"%/%[%]%?%=%{%}]' -local function unquote(t, quoted) +local function unquote(t, quoted) local n = string.match(t, "%$(%d+)$") if n then n = tonumber(n) end if quoted[n] then return quoted[n] @@ -14,19 +14,19 @@ end local function parse_set_cookie(c, quoted, cookie_table) c = c .. ";$last=last;" - local _, __, n, v, i = string.find(c, "(" .. token_class .. + local _, _, n, v, i = string.find(c, "(" .. token_class .. "+)%s*=%s*(.-)%s*;%s*()") local cookie = { - name = n, - value = unquote(v, quoted), + name = n, + value = unquote(v, quoted), attributes = {} } while 1 do - _, __, n, v, i = string.find(c, "(" .. token_class .. + _, _, n, v, i = string.find(c, "(" .. token_class .. "+)%s*=?%s*(.-)%s*;%s*()", i) if not n or n == "$last" then break end cookie.attributes[#cookie.attributes+1] = { - name = n, + name = n, value = unquote(v, quoted) } end @@ -46,8 +46,8 @@ local function split_set_cookie(s, cookie_table) -- split into individual cookies i = 1 while 1 do - local _, __, cookie, next_token - _, __, cookie, i, next_token = string.find(s, "(.-)%s*%,%s*()(" .. + local _, _, cookie, next_token + _, _, cookie, i, next_token = string.find(s, "(.-)%s*%,%s*()(" .. token_class .. "+)%s*=", i) if not next_token then break end parse_set_cookie(cookie, quoted, cookie_table) @@ -62,12 +62,12 @@ local function quote(s) end local _empty = {} -local function build_cookies(cookies) +local function build_cookies(cookies) s = "" for i,v in ipairs(cookies or _empty) do if v.name then s = s .. v.name - if v.value and v.value ~= "" then + if v.value and v.value ~= "" then s = s .. '=' .. quote(v.value) end end @@ -83,6 +83,6 @@ local function build_cookies(cookies) end if i < #cookies then s = s .. ", " end end - return s + return s end diff --git a/etc/get.lua b/etc/get.lua index 9edc235..d53c465 100644 --- a/etc/get.lua +++ b/etc/get.lua @@ -71,7 +71,7 @@ function stats(size) local current = socket.gettime() if chunk then -- total bytes received - got = got + string.len(chunk) + got = got + string.len(chunk) -- not enough time for estimate if current - last > 1 then io.stderr:write("\r", gauge(got, current - start, size)) -- cgit v1.2.3-55-g6feb From 86de838eb5ed49711be8d62e01255cc2ccd3342e Mon Sep 17 00:00:00 2001 From: Thijs Schreijer <thijs@thijsschreijer.nl> Date: Wed, 23 Mar 2022 16:05:11 +0100 Subject: cleanup; move ./etc into ./samples and mark 'unsupported' --- .luacheckrc | 2 - etc/README | 89 ------------- etc/b64.lua | 19 --- etc/check-links.lua | 111 ---------------- etc/check-memory.lua | 17 --- etc/cookie.lua | 88 ------------- etc/dict.lua | 151 ---------------------- etc/dispatch.lua | 307 -------------------------------------------- etc/eol.lua | 13 -- etc/forward.lua | 65 ---------- etc/get.lua | 141 --------------------- etc/links | 17 --- etc/lp.lua | 323 ----------------------------------------------- etc/qp.lua | 23 ---- etc/tftp.lua | 154 ---------------------- luasocket-scm-3.rockspec | 1 - makefile.dist | 28 ++-- samples/README | 90 ++++++++++++- samples/b64.lua | 19 +++ samples/check-links.lua | 111 ++++++++++++++++ samples/check-memory.lua | 17 +++ samples/cookie.lua | 88 +++++++++++++ samples/dict.lua | 151 ++++++++++++++++++++++ samples/dispatch.lua | 307 ++++++++++++++++++++++++++++++++++++++++++++ samples/eol.lua | 13 ++ samples/forward.lua | 65 ++++++++++ samples/get.lua | 141 +++++++++++++++++++++ samples/links | 17 +++ samples/lp.lua | 323 +++++++++++++++++++++++++++++++++++++++++++++++ samples/qp.lua | 23 ++++ samples/tftp.lua | 154 ++++++++++++++++++++++ 31 files changed, 1527 insertions(+), 1541 deletions(-) delete mode 100644 etc/README delete mode 100644 etc/b64.lua delete mode 100644 etc/check-links.lua delete mode 100644 etc/check-memory.lua delete mode 100644 etc/cookie.lua delete mode 100644 etc/dict.lua delete mode 100644 etc/dispatch.lua delete mode 100644 etc/eol.lua delete mode 100644 etc/forward.lua delete mode 100644 etc/get.lua delete mode 100644 etc/links delete mode 100644 etc/lp.lua delete mode 100644 etc/qp.lua delete mode 100644 etc/tftp.lua create mode 100644 samples/b64.lua create mode 100644 samples/check-links.lua create mode 100644 samples/check-memory.lua create mode 100644 samples/cookie.lua create mode 100644 samples/dict.lua create mode 100644 samples/dispatch.lua create mode 100644 samples/eol.lua create mode 100644 samples/forward.lua create mode 100644 samples/get.lua create mode 100644 samples/links create mode 100644 samples/lp.lua create mode 100644 samples/qp.lua create mode 100644 samples/tftp.lua (limited to 'etc') diff --git a/.luacheckrc b/.luacheckrc index 8b25dd7..a3b4f63 100644 --- a/.luacheckrc +++ b/.luacheckrc @@ -15,8 +15,6 @@ include_files = { } exclude_files = { - "etc/*.lua", - "etc/**/*.lua", "test/*.lua", "test/**/*.lua", "samples/*.lua", diff --git a/etc/README b/etc/README deleted file mode 100644 index cfd3e37..0000000 --- a/etc/README +++ /dev/null @@ -1,89 +0,0 @@ -This directory contains code that is more useful than the -samples. This code *is* supported. - - tftp.lua -- Trivial FTP client - -This module implements file retrieval by the TFTP protocol. -Its main use was to test the UDP code, but since someone -found it usefull, I turned it into a module that is almost -official (no uploads, yet). - - dict.lua -- Dict client - -The dict.lua module started with a cool simple client -for the DICT protocol, written by Luiz Henrique Figueiredo. -This new version has been converted into a library, similar -to the HTTP and FTP libraries, that can be used from within -any luasocket application. Take a look on the source code -and you will be able to figure out how to use it. - - lp.lua -- LPD client library - -The lp.lua module implements the client part of the Line -Printer Daemon protocol, used to print files on Unix -machines. It is courtesy of David Burgess! See the source -code and the lpr.lua in the examples directory. - - b64.lua - qp.lua - eol.lua - -These are tiny programs that perform Base64, -Quoted-Printable and end-of-line marker conversions. - - get.lua -- file retriever - -This little program is a client that uses the FTP and -HTTP code to implement a command line file graber. Just -run - - lua get.lua <remote-file> [<local-file>] - -to download a remote file (either ftp:// or http://) to -the specified local file. The program also prints the -download throughput, elapsed time, bytes already downloaded -etc during download. - - check-memory.lua -- checks memory consumption - -This is just to see how much memory each module uses. - - dispatch.lua -- coroutine based dispatcher - -This is a first try at a coroutine based non-blocking -dispatcher for LuaSocket. Take a look at 'check-links.lua' -and at 'forward.lua' to see how to use it. - - check-links.lua -- HTML link checker program - -This little program scans a HTML file and checks for broken -links. It is similar to check-links.pl by Jamie Zawinski, -but uses all facilities of the LuaSocket library and the Lua -language. It has not been thoroughly tested, but it should -work. Just run - - lua check-links.lua [-n] {<url>} > output - -and open the result to see a list of broken links. Make sure -you check the '-n' switch. It runs in non-blocking mode, -using coroutines, and is MUCH faster! - - forward.lua -- coroutine based forward server - -This is a forward server that can accept several connections -and transfers simultaneously using non-blocking I/O and the -coroutine-based dispatcher. You can run, for example - - lua forward.lua 8080:proxy.com:3128 - -to redirect all local conections to port 8080 to the host -'proxy.com' at port 3128. - - unix.c and unix.h - -This is an implementation of Unix local domain sockets and -demonstrates how to extend LuaSocket with a new type of -transport. It has been tested on Linux and on Mac OS X. - -Good luck, -Diego. diff --git a/etc/b64.lua b/etc/b64.lua deleted file mode 100644 index 11eeb2d..0000000 --- a/etc/b64.lua +++ /dev/null @@ -1,19 +0,0 @@ ------------------------------------------------------------------------------ --- Little program to convert to and from Base64 --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local ltn12 = require("ltn12") -local mime = require("mime") -local source = ltn12.source.file(io.stdin) -local sink = ltn12.sink.file(io.stdout) -local convert -if arg and arg[1] == '-d' then - convert = mime.decode("base64") -else - local base64 = mime.encode("base64") - local wrap = mime.wrap() - convert = ltn12.filter.chain(base64, wrap) -end -sink = ltn12.sink.chain(convert, sink) -ltn12.pump.all(source, sink) diff --git a/etc/check-links.lua b/etc/check-links.lua deleted file mode 100644 index 283f3ac..0000000 --- a/etc/check-links.lua +++ /dev/null @@ -1,111 +0,0 @@ ------------------------------------------------------------------------------ --- Little program that checks links in HTML files, using coroutines and --- non-blocking I/O via the dispatcher module. --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local url = require("socket.url") -local dispatch = require("dispatch") -local http = require("socket.http") -dispatch.TIMEOUT = 10 - --- make sure the user knows how to invoke us -arg = arg or {} -if #arg < 1 then - print("Usage:\n luasocket check-links.lua [-n] {<url>}") - exit() -end - --- '-n' means we are running in non-blocking mode -if arg[1] == "-n" then - -- if non-blocking I/O was requested, use real dispatcher interface - table.remove(arg, 1) - handler = dispatch.newhandler("coroutine") -else - -- if using blocking I/O, use fake dispatcher interface - handler = dispatch.newhandler("sequential") -end - -local nthreads = 0 - --- get the status of a URL using the dispatcher -function getstatus(link) - local parsed = url.parse(link, {scheme = "file"}) - if parsed.scheme == "http" then - nthreads = nthreads + 1 - handler:start(function() - local r, c, h, s = http.request{ - method = "HEAD", - url = link, - create = handler.tcp - } - if r and c == 200 then io.write('\t', link, '\n') - else io.write('\t', link, ': ', tostring(c), '\n') end - nthreads = nthreads - 1 - end) - end -end - -function readfile(path) - path = url.unescape(path) - local file, error = io.open(path, "r") - if file then - local body = file:read("*a") - file:close() - return body - else return nil, error end -end - -function load(u) - local parsed = url.parse(u, { scheme = "file" }) - local body, headers, code, error - local base = u - if parsed.scheme == "http" then - body, code, headers = http.request(u) - if code == 200 then - -- if there was a redirect, update base to reflect it - base = headers.location or base - end - if not body then - error = code - end - elseif parsed.scheme == "file" then - body, error = readfile(parsed.path) - else error = string.format("unhandled scheme '%s'", parsed.scheme) end - return base, body, error -end - -function getlinks(body, base) - -- get rid of comments - body = string.gsub(body, "%<%!%-%-.-%-%-%>", "") - local links = {} - -- extract links - body = string.gsub(body, '[Hh][Rr][Ee][Ff]%s*=%s*"([^"]*)"', function(href) - table.insert(links, url.absolute(base, href)) - end) - body = string.gsub(body, "[Hh][Rr][Ee][Ff]%s*=%s*'([^']*)'", function(href) - table.insert(links, url.absolute(base, href)) - end) - string.gsub(body, "[Hh][Rr][Ee][Ff]%s*=%s*(.-)>", function(href) - table.insert(links, url.absolute(base, href)) - end) - return links -end - -function checklinks(address) - local base, body, error = load(address) - if not body then print(error) return end - print("Checking ", base) - local links = getlinks(body, base) - for _, link in ipairs(links) do - getstatus(link) - end -end - -for _, address in ipairs(arg) do - checklinks(url.absolute("file:", address)) -end - -while nthreads > 0 do - handler:step() -end diff --git a/etc/check-memory.lua b/etc/check-memory.lua deleted file mode 100644 index 7bd984d..0000000 --- a/etc/check-memory.lua +++ /dev/null @@ -1,17 +0,0 @@ -function load(s) - collectgarbage() - local a = gcinfo() - _G[s] = require(s) - collectgarbage() - local b = gcinfo() - print(s .. ":\t " .. (b-a) .. "k") -end - -load("socket.url") -load("ltn12") -load("socket") -load("mime") -load("socket.tp") -load("socket.smtp") -load("socket.http") -load("socket.ftp") diff --git a/etc/cookie.lua b/etc/cookie.lua deleted file mode 100644 index fec10a1..0000000 --- a/etc/cookie.lua +++ /dev/null @@ -1,88 +0,0 @@ -local socket = require"socket" -local http = require"socket.http" -local url = require"socket.url" -local ltn12 = require"ltn12" - -local token_class = '[^%c%s%(%)%<%>%@%,%;%:%\\%"%/%[%]%?%=%{%}]' - -local function unquote(t, quoted) - local n = string.match(t, "%$(%d+)$") - if n then n = tonumber(n) end - if quoted[n] then return quoted[n] - else return t end -end - -local function parse_set_cookie(c, quoted, cookie_table) - c = c .. ";$last=last;" - local _, _, n, v, i = string.find(c, "(" .. token_class .. - "+)%s*=%s*(.-)%s*;%s*()") - local cookie = { - name = n, - value = unquote(v, quoted), - attributes = {} - } - while 1 do - _, _, n, v, i = string.find(c, "(" .. token_class .. - "+)%s*=?%s*(.-)%s*;%s*()", i) - if not n or n == "$last" then break end - cookie.attributes[#cookie.attributes+1] = { - name = n, - value = unquote(v, quoted) - } - end - cookie_table[#cookie_table+1] = cookie -end - -local function split_set_cookie(s, cookie_table) - cookie_table = cookie_table or {} - -- remove quoted strings from cookie list - local quoted = {} - s = string.gsub(s, '"(.-)"', function(q) - quoted[#quoted+1] = q - return "$" .. #quoted - end) - -- add sentinel - s = s .. ",$last=" - -- split into individual cookies - i = 1 - while 1 do - local _, _, cookie, next_token - _, _, cookie, i, next_token = string.find(s, "(.-)%s*%,%s*()(" .. - token_class .. "+)%s*=", i) - if not next_token then break end - parse_set_cookie(cookie, quoted, cookie_table) - if next_token == "$last" then break end - end - return cookie_table -end - -local function quote(s) - if string.find(s, "[ %,%;]") then return '"' .. s .. '"' - else return s end -end - -local _empty = {} -local function build_cookies(cookies) - s = "" - for i,v in ipairs(cookies or _empty) do - if v.name then - s = s .. v.name - if v.value and v.value ~= "" then - s = s .. '=' .. quote(v.value) - end - end - if v.name and #(v.attributes or _empty) > 0 then s = s .. "; " end - for j,u in ipairs(v.attributes or _empty) do - if u.name then - s = s .. u.name - if u.value and u.value ~= "" then - s = s .. '=' .. quote(u.value) - end - end - if j < #v.attributes then s = s .. "; " end - end - if i < #cookies then s = s .. ", " end - end - return s -end - diff --git a/etc/dict.lua b/etc/dict.lua deleted file mode 100644 index 8c5b711..0000000 --- a/etc/dict.lua +++ /dev/null @@ -1,151 +0,0 @@ ------------------------------------------------------------------------------ --- Little program to download DICT word definitions --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ - ------------------------------------------------------------------------------ --- Load required modules ------------------------------------------------------------------------------ -local base = _G -local string = require("string") -local table = require("table") -local socket = require("socket") -local url = require("socket.url") -local tp = require("socket.tp") -module("socket.dict") - ------------------------------------------------------------------------------ --- Globals ------------------------------------------------------------------------------ -HOST = "dict.org" -PORT = 2628 -TIMEOUT = 10 - ------------------------------------------------------------------------------ --- Low-level dict API ------------------------------------------------------------------------------ -local metat = { __index = {} } - -function open(host, port) - local tp = socket.try(tp.connect(host or HOST, port or PORT, TIMEOUT)) - return base.setmetatable({tp = tp}, metat) -end - -function metat.__index:greet() - return socket.try(self.tp:check(220)) -end - -function metat.__index:check(ok) - local code, status = socket.try(self.tp:check(ok)) - return code, - base.tonumber(socket.skip(2, string.find(status, "^%d%d%d (%d*)"))) -end - -function metat.__index:getdef() - local line = socket.try(self.tp:receive()) - local def = {} - while line ~= "." do - table.insert(def, line) - line = socket.try(self.tp:receive()) - end - return table.concat(def, "\n") -end - -function metat.__index:define(database, word) - database = database or "!" - socket.try(self.tp:command("DEFINE", database .. " " .. word)) - local code, count = self:check(150) - local defs = {} - for i = 1, count do - self:check(151) - table.insert(defs, self:getdef()) - end - self:check(250) - return defs -end - -function metat.__index:match(database, strat, word) - database = database or "!" - strat = strat or "." - socket.try(self.tp:command("MATCH", database .." ".. strat .." ".. word)) - self:check(152) - local mat = {} - local line = socket.try(self.tp:receive()) - while line ~= '.' do - database, word = socket.skip(2, string.find(line, "(%S+) (.*)")) - if not mat[database] then mat[database] = {} end - table.insert(mat[database], word) - line = socket.try(self.tp:receive()) - end - self:check(250) - return mat -end - -function metat.__index:quit() - self.tp:command("QUIT") - return self:check(221) -end - -function metat.__index:close() - return self.tp:close() -end - ------------------------------------------------------------------------------ --- High-level dict API ------------------------------------------------------------------------------ -local default = { - scheme = "dict", - host = "dict.org" -} - -local function there(f) - if f == "" then return nil - else return f end -end - -local function parse(u) - local t = socket.try(url.parse(u, default)) - socket.try(t.scheme == "dict", "invalid scheme '" .. t.scheme .. "'") - socket.try(t.path, "invalid path in url") - local cmd, arg = socket.skip(2, string.find(t.path, "^/(.)(.*)$")) - socket.try(cmd == "d" or cmd == "m", "<command> should be 'm' or 'd'") - socket.try(arg and arg ~= "", "need at least <word> in URL") - t.command, t.argument = cmd, arg - arg = string.gsub(arg, "^:([^:]+)", function(f) t.word = f end) - socket.try(t.word, "need at least <word> in URL") - arg = string.gsub(arg, "^:([^:]*)", function(f) t.database = there(f) end) - if cmd == "m" then - arg = string.gsub(arg, "^:([^:]*)", function(f) t.strat = there(f) end) - end - string.gsub(arg, ":([^:]*)$", function(f) t.n = base.tonumber(f) end) - return t -end - -local function tget(gett) - local con = open(gett.host, gett.port) - con:greet() - if gett.command == "d" then - local def = con:define(gett.database, gett.word) - con:quit() - con:close() - if gett.n then return def[gett.n] - else return def end - elseif gett.command == "m" then - local mat = con:match(gett.database, gett.strat, gett.word) - con:quit() - con:close() - return mat - else return nil, "invalid command" end -end - -local function sget(u) - local gett = parse(u) - return tget(gett) -end - -get = socket.protect(function(gett) - if base.type(gett) == "string" then return sget(gett) - else return tget(gett) end -end) - diff --git a/etc/dispatch.lua b/etc/dispatch.lua deleted file mode 100644 index 2485415..0000000 --- a/etc/dispatch.lua +++ /dev/null @@ -1,307 +0,0 @@ ------------------------------------------------------------------------------ --- A hacked dispatcher module --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local base = _G -local table = require("table") -local string = require("string") -local socket = require("socket") -local coroutine = require("coroutine") -module("dispatch") - --- if too much time goes by without any activity in one of our sockets, we --- just kill it -TIMEOUT = 60 - ------------------------------------------------------------------------------ --- We implement 3 types of dispatchers: --- sequential --- coroutine --- threaded --- The user can choose whatever one is needed ------------------------------------------------------------------------------ -local handlert = {} - --- default handler is coroutine -function newhandler(mode) - mode = mode or "coroutine" - return handlert[mode]() -end - -local function seqstart(self, func) - return func() -end - --- sequential handler simply calls the functions and doesn't wrap I/O -function handlert.sequential() - return { - tcp = socket.tcp, - start = seqstart - } -end - ------------------------------------------------------------------------------ --- Mega hack. Don't try to do this at home. ------------------------------------------------------------------------------ --- we can't yield across calls to protect on Lua 5.1, so we rewrite it with --- coroutines --- make sure you don't require any module that uses socket.protect before --- loading our hack -if string.sub(base._VERSION, -3) == "5.1" then - local function _protect(co, status, ...) - if not status then - local msg = ... - if base.type(msg) == 'table' then - return nil, msg[1] - else - base.error(msg, 0) - end - end - if coroutine.status(co) == "suspended" then - return _protect(co, coroutine.resume(co, coroutine.yield(...))) - else - return ... - end - end - - function socket.protect(f) - return function(...) - local co = coroutine.create(f) - return _protect(co, coroutine.resume(co, ...)) - end - end -end - ------------------------------------------------------------------------------ --- Simple set data structure. O(1) everything. ------------------------------------------------------------------------------ -local function newset() - local reverse = {} - local set = {} - return base.setmetatable(set, {__index = { - insert = function(set, value) - if not reverse[value] then - table.insert(set, value) - reverse[value] = #set - end - end, - remove = function(set, value) - local index = reverse[value] - if index then - reverse[value] = nil - local top = table.remove(set) - if top ~= value then - reverse[top] = index - set[index] = top - end - end - end - }}) -end - ------------------------------------------------------------------------------ --- socket.tcp() wrapper for the coroutine dispatcher ------------------------------------------------------------------------------ -local function cowrap(dispatcher, tcp, error) - if not tcp then return nil, error end - -- put it in non-blocking mode right away - tcp:settimeout(0) - -- metatable for wrap produces new methods on demand for those that we - -- don't override explicitly. - local metat = { __index = function(table, key) - table[key] = function(...) - return tcp[key](tcp,select(2,...)) - end - return table[key] - end} - -- does our user want to do his own non-blocking I/O? - local zero = false - -- create a wrap object that will behave just like a real socket object - local wrap = { } - -- we ignore settimeout to preserve our 0 timeout, but record whether - -- the user wants to do his own non-blocking I/O - function wrap:settimeout(value, mode) - if value == 0 then zero = true - else zero = false end - return 1 - end - -- send in non-blocking mode and yield on timeout - function wrap:send(data, first, last) - first = (first or 1) - 1 - local result, error - while true do - -- return control to dispatcher and tell it we want to send - -- if upon return the dispatcher tells us we timed out, - -- return an error to whoever called us - if coroutine.yield(dispatcher.sending, tcp) == "timeout" then - return nil, "timeout" - end - -- try sending - result, error, first = tcp:send(data, first+1, last) - -- if we are done, or there was an unexpected error, - -- break away from loop - if error ~= "timeout" then return result, error, first end - end - end - -- receive in non-blocking mode and yield on timeout - -- or simply return partial read, if user requested timeout = 0 - function wrap:receive(pattern, partial) - local error = "timeout" - local value - while true do - -- return control to dispatcher and tell it we want to receive - -- if upon return the dispatcher tells us we timed out, - -- return an error to whoever called us - if coroutine.yield(dispatcher.receiving, tcp) == "timeout" then - return nil, "timeout" - end - -- try receiving - value, error, partial = tcp:receive(pattern, partial) - -- if we are done, or there was an unexpected error, - -- break away from loop. also, if the user requested - -- zero timeout, return all we got - if (error ~= "timeout") or zero then - return value, error, partial - end - end - end - -- connect in non-blocking mode and yield on timeout - function wrap:connect(host, port) - local result, error = tcp:connect(host, port) - if error == "timeout" then - -- return control to dispatcher. we will be writable when - -- connection succeeds. - -- if upon return the dispatcher tells us we have a - -- timeout, just abort - if coroutine.yield(dispatcher.sending, tcp) == "timeout" then - return nil, "timeout" - end - -- when we come back, check if connection was successful - result, error = tcp:connect(host, port) - if result or error == "already connected" then return 1 - else return nil, "non-blocking connect failed" end - else return result, error end - end - -- accept in non-blocking mode and yield on timeout - function wrap:accept() - while 1 do - -- return control to dispatcher. we will be readable when a - -- connection arrives. - -- if upon return the dispatcher tells us we have a - -- timeout, just abort - if coroutine.yield(dispatcher.receiving, tcp) == "timeout" then - return nil, "timeout" - end - local client, error = tcp:accept() - if error ~= "timeout" then - return cowrap(dispatcher, client, error) - end - end - end - -- remove cortn from context - function wrap:close() - dispatcher.stamp[tcp] = nil - dispatcher.sending.set:remove(tcp) - dispatcher.sending.cortn[tcp] = nil - dispatcher.receiving.set:remove(tcp) - dispatcher.receiving.cortn[tcp] = nil - return tcp:close() - end - return base.setmetatable(wrap, metat) -end - - ------------------------------------------------------------------------------ --- Our coroutine dispatcher ------------------------------------------------------------------------------ -local cometat = { __index = {} } - -function schedule(cortn, status, operation, tcp) - if status then - if cortn and operation then - operation.set:insert(tcp) - operation.cortn[tcp] = cortn - operation.stamp[tcp] = socket.gettime() - end - else base.error(operation) end -end - -function kick(operation, tcp) - operation.cortn[tcp] = nil - operation.set:remove(tcp) -end - -function wakeup(operation, tcp) - local cortn = operation.cortn[tcp] - -- if cortn is still valid, wake it up - if cortn then - kick(operation, tcp) - return cortn, coroutine.resume(cortn) - -- othrewise, just get scheduler not to do anything - else - return nil, true - end -end - -function abort(operation, tcp) - local cortn = operation.cortn[tcp] - if cortn then - kick(operation, tcp) - coroutine.resume(cortn, "timeout") - end -end - --- step through all active cortns -function cometat.__index:step() - -- check which sockets are interesting and act on them - local readable, writable = socket.select(self.receiving.set, - self.sending.set, 1) - -- for all readable connections, resume their cortns and reschedule - -- when they yield back to us - for _, tcp in base.ipairs(readable) do - schedule(wakeup(self.receiving, tcp)) - end - -- for all writable connections, do the same - for _, tcp in base.ipairs(writable) do - schedule(wakeup(self.sending, tcp)) - end - -- politely ask replacement I/O functions in idle cortns to - -- return reporting a timeout - local now = socket.gettime() - for tcp, stamp in base.pairs(self.stamp) do - if tcp.class == "tcp{client}" and now - stamp > TIMEOUT then - abort(self.sending, tcp) - abort(self.receiving, tcp) - end - end -end - -function cometat.__index:start(func) - local cortn = coroutine.create(func) - schedule(cortn, coroutine.resume(cortn)) -end - -function handlert.coroutine() - local stamp = {} - local dispatcher = { - stamp = stamp, - sending = { - name = "sending", - set = newset(), - cortn = {}, - stamp = stamp - }, - receiving = { - name = "receiving", - set = newset(), - cortn = {}, - stamp = stamp - }, - } - function dispatcher.tcp() - return cowrap(dispatcher, socket.tcp()) - end - return base.setmetatable(dispatcher, cometat) -end - diff --git a/etc/eol.lua b/etc/eol.lua deleted file mode 100644 index eeaf0ce..0000000 --- a/etc/eol.lua +++ /dev/null @@ -1,13 +0,0 @@ ------------------------------------------------------------------------------ --- Little program to adjust end of line markers. --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local mime = require("mime") -local ltn12 = require("ltn12") -local marker = '\n' -if arg and arg[1] == '-d' then marker = '\r\n' end -local filter = mime.normalize(marker) -local source = ltn12.source.chain(ltn12.source.file(io.stdin), filter) -local sink = ltn12.sink.file(io.stdout) -ltn12.pump.all(source, sink) diff --git a/etc/forward.lua b/etc/forward.lua deleted file mode 100644 index 05ced1a..0000000 --- a/etc/forward.lua +++ /dev/null @@ -1,65 +0,0 @@ --- load our favourite library -local dispatch = require("dispatch") -local handler = dispatch.newhandler() - --- make sure the user knows how to invoke us -if #arg < 1 then - print("Usage") - print(" lua forward.lua <iport:ohost:oport> ...") - os.exit(1) -end - --- function to move data from one socket to the other -local function move(foo, bar) - local live - while 1 do - local data, error, partial = foo:receive(2048) - live = data or error == "timeout" - data = data or partial - local result, error = bar:send(data) - if not live or not result then - foo:close() - bar:close() - break - end - end -end - --- for each tunnel, start a new server -for i, v in ipairs(arg) do - -- capture forwarding parameters - local _, _, iport, ohost, oport = string.find(v, "([^:]+):([^:]+):([^:]+)") - assert(iport, "invalid arguments") - -- create our server socket - local server = assert(handler.tcp()) - assert(server:setoption("reuseaddr", true)) - assert(server:bind("*", iport)) - assert(server:listen(32)) - -- handler for the server object loops accepting new connections - handler:start(function() - while 1 do - local client = assert(server:accept()) - assert(client:settimeout(0)) - -- for each new connection, start a new client handler - handler:start(function() - -- handler tries to connect to peer - local peer = assert(handler.tcp()) - assert(peer:settimeout(0)) - assert(peer:connect(ohost, oport)) - -- if sucessful, starts a new handler to send data from - -- client to peer - handler:start(function() - move(client, peer) - end) - -- afte starting new handler, enter in loop sending data from - -- peer to client - move(peer, client) - end) - end - end) -end - --- simply loop stepping the server -while 1 do - handler:step() -end diff --git a/etc/get.lua b/etc/get.lua deleted file mode 100644 index d53c465..0000000 --- a/etc/get.lua +++ /dev/null @@ -1,141 +0,0 @@ ------------------------------------------------------------------------------ --- Little program to download files from URLs --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local socket = require("socket") -local http = require("socket.http") -local ftp = require("socket.ftp") -local url = require("socket.url") -local ltn12 = require("ltn12") - --- formats a number of seconds into human readable form -function nicetime(s) - local l = "s" - if s > 60 then - s = s / 60 - l = "m" - if s > 60 then - s = s / 60 - l = "h" - if s > 24 then - s = s / 24 - l = "d" -- hmmm - end - end - end - if l == "s" then return string.format("%5.0f%s", s, l) - else return string.format("%5.2f%s", s, l) end -end - --- formats a number of bytes into human readable form -function nicesize(b) - local l = "B" - if b > 1024 then - b = b / 1024 - l = "KB" - if b > 1024 then - b = b / 1024 - l = "MB" - if b > 1024 then - b = b / 1024 - l = "GB" -- hmmm - end - end - end - return string.format("%7.2f%2s", b, l) -end - --- returns a string with the current state of the download -local remaining_s = "%s received, %s/s throughput, %2.0f%% done, %s remaining" -local elapsed_s = "%s received, %s/s throughput, %s elapsed " -function gauge(got, delta, size) - local rate = got / delta - if size and size >= 1 then - return string.format(remaining_s, nicesize(got), nicesize(rate), - 100*got/size, nicetime((size-got)/rate)) - else - return string.format(elapsed_s, nicesize(got), - nicesize(rate), nicetime(delta)) - end -end - --- creates a new instance of a receive_cb that saves to disk --- kind of copied from luasocket's manual callback examples -function stats(size) - local start = socket.gettime() - local last = start - local got = 0 - return function(chunk) - -- elapsed time since start - local current = socket.gettime() - if chunk then - -- total bytes received - got = got + string.len(chunk) - -- not enough time for estimate - if current - last > 1 then - io.stderr:write("\r", gauge(got, current - start, size)) - io.stderr:flush() - last = current - end - else - -- close up - io.stderr:write("\r", gauge(got, current - start), "\n") - end - return chunk - end -end - --- determines the size of a http file -function gethttpsize(u) - local r, c, h = http.request {method = "HEAD", url = u} - if c == 200 then - return tonumber(h["content-length"]) - end -end - --- downloads a file using the http protocol -function getbyhttp(u, file) - local save = ltn12.sink.file(file or io.stdout) - -- only print feedback if output is not stdout - if file then save = ltn12.sink.chain(stats(gethttpsize(u)), save) end - local r, c, h, s = http.request {url = u, sink = save } - if c ~= 200 then io.stderr:write(s or c, "\n") end -end - --- downloads a file using the ftp protocol -function getbyftp(u, file) - local save = ltn12.sink.file(file or io.stdout) - -- only print feedback if output is not stdout - -- and we don't know how big the file is - if file then save = ltn12.sink.chain(stats(), save) end - local gett = url.parse(u) - gett.sink = save - gett.type = "i" - local ret, err = ftp.get(gett) - if err then print(err) end -end - --- determines the scheme -function getscheme(u) - -- this is an heuristic to solve a common invalid url poblem - if not string.find(u, "//") then u = "//" .. u end - local parsed = url.parse(u, {scheme = "http"}) - return parsed.scheme -end - --- gets a file either by http or ftp, saving as <name> -function get(u, name) - local fout = name and io.open(name, "wb") - local scheme = getscheme(u) - if scheme == "ftp" then getbyftp(u, fout) - elseif scheme == "http" then getbyhttp(u, fout) - else print("unknown scheme" .. scheme) end -end - --- main program -arg = arg or {} -if #arg < 1 then - io.write("Usage:\n lua get.lua <remote-url> [<local-file>]\n") - os.exit(1) -else get(arg[1], arg[2]) end diff --git a/etc/links b/etc/links deleted file mode 100644 index 087f1c0..0000000 --- a/etc/links +++ /dev/null @@ -1,17 +0,0 @@ -<a href="http://www.cs.princeton.edu"> bla </a> -<a href="http://www.princeton.edu"> bla </a> -<a href="http://www.tecgraf.puc-rio.br"> bla </a> -<a href="http://www.inf.puc-rio.br"> bla </a> -<a href="http://www.puc-rio.br"> bla </a> -<a href="http://www.impa.br"> bla </a> -<a href="http://www.lua.org"> bla </a> -<a href="http://www.lua-users.org"> bla </a> -<a href="http://www.amazon.com"> bla </a> -<a href="http://www.google.com"> bla </a> -<a href="http://www.nytimes.com"> bla </a> -<a href="http://www.bbc.co.uk"> bla </a> -<a href="http://oglobo.globo.com"> bla </a> -<a href="http://slate.msn.com"> bla </a> -<a href="http://www.apple.com"> bla </a> -<a href="http://www.microsoft.com"> bla </a> -<a href="http://www.nasa.gov"> bla </a> diff --git a/etc/lp.lua b/etc/lp.lua deleted file mode 100644 index 25f0b95..0000000 --- a/etc/lp.lua +++ /dev/null @@ -1,323 +0,0 @@ ------------------------------------------------------------------------------ --- LPD support for the Lua language --- LuaSocket toolkit. --- Author: David Burgess --- Modified by Diego Nehab, but David is in charge ------------------------------------------------------------------------------ ---[[ - if you have any questions: RFC 1179 -]] --- make sure LuaSocket is loaded -local io = require("io") -local base = _G -local os = require("os") -local math = require("math") -local string = require("string") -local socket = require("socket") -local ltn12 = require("ltn12") -module("socket.lp") - --- default port -PORT = 515 -SERVER = os.getenv("SERVER_NAME") or os.getenv("COMPUTERNAME") or "localhost" -PRINTER = os.getenv("PRINTER") or "printer" - -local function connect(localhost, option) - local host = option.host or SERVER - local port = option.port or PORT - local skt - local try = socket.newtry(function() if skt then skt:close() end end) - if option.localbind then - -- bind to a local port (if we can) - local localport = 721 - local done, err - repeat - skt = socket.try(socket.tcp()) - try(skt:settimeout(30)) - done, err = skt:bind(localhost, localport) - if not done then - localport = localport + 1 - skt:close() - skt = nil - else break end - until localport > 731 - socket.try(skt, err) - else skt = socket.try(socket.tcp()) end - try(skt:connect(host, port)) - return { skt = skt, try = try } -end - ---[[ -RFC 1179 -5.3 03 - Send queue state (short) - - +----+-------+----+------+----+ - | 03 | Queue | SP | List | LF | - +----+-------+----+------+----+ - Command code - 3 - Operand 1 - Printer queue name - Other operands - User names or job numbers - - If the user names or job numbers or both are supplied then only those - jobs for those users or with those numbers will be sent. - - The response is an ASCII stream which describes the printer queue. - The stream continues until the connection closes. Ends of lines are - indicated with ASCII LF control characters. The lines may also - contain ASCII HT control characters. - -5.4 04 - Send queue state (long) - - +----+-------+----+------+----+ - | 04 | Queue | SP | List | LF | - +----+-------+----+------+----+ - Command code - 4 - Operand 1 - Printer queue name - Other operands - User names or job numbers - - If the user names or job numbers or both are supplied then only those - jobs for those users or with those numbers will be sent. - - The response is an ASCII stream which describes the printer queue. - The stream continues until the connection closes. Ends of lines are - indicated with ASCII LF control characters. The lines may also - contain ASCII HT control characters. -]] - --- gets server acknowledement -local function recv_ack(con) - local ack = con.skt:receive(1) - con.try(string.char(0) == ack, "failed to receive server acknowledgement") -end - --- sends client acknowledement -local function send_ack(con) - local sent = con.skt:send(string.char(0)) - con.try(sent == 1, "failed to send acknowledgement") -end - --- sends queue request --- 5.2 02 - Receive a printer job --- --- +----+-------+----+ --- | 02 | Queue | LF | --- +----+-------+----+ --- Command code - 2 --- Operand - Printer queue name --- --- Receiving a job is controlled by a second level of commands. The --- daemon is given commands by sending them over the same connection. --- The commands are described in the next section (6). --- --- After this command is sent, the client must read an acknowledgement --- octet from the daemon. A positive acknowledgement is an octet of --- zero bits. A negative acknowledgement is an octet of any other --- pattern. -local function send_queue(con, queue) - queue = queue or PRINTER - local str = string.format("\2%s\10", queue) - local sent = con.skt:send(str) - con.try(sent == string.len(str), "failed to send print request") - recv_ack(con) -end - --- sends control file --- 6.2 02 - Receive control file --- --- +----+-------+----+------+----+ --- | 02 | Count | SP | Name | LF | --- +----+-------+----+------+----+ --- Command code - 2 --- Operand 1 - Number of bytes in control file --- Operand 2 - Name of control file --- --- The control file must be an ASCII stream with the ends of lines --- indicated by ASCII LF. The total number of bytes in the stream is --- sent as the first operand. The name of the control file is sent as --- the second. It should start with ASCII "cfA", followed by a three --- digit job number, followed by the host name which has constructed the --- control file. Acknowledgement processing must occur as usual after --- the command is sent. --- --- The next "Operand 1" octets over the same TCP connection are the --- intended contents of the control file. Once all of the contents have --- been delivered, an octet of zero bits is sent as an indication that --- the file being sent is complete. A second level of acknowledgement --- processing must occur at this point. - --- sends data file --- 6.3 03 - Receive data file --- --- +----+-------+----+------+----+ --- | 03 | Count | SP | Name | LF | --- +----+-------+----+------+----+ --- Command code - 3 --- Operand 1 - Number of bytes in data file --- Operand 2 - Name of data file --- --- The data file may contain any 8 bit values at all. The total number --- of bytes in the stream may be sent as the first operand, otherwise --- the field should be cleared to 0. The name of the data file should --- start with ASCII "dfA". This should be followed by a three digit job --- number. The job number should be followed by the host name which has --- constructed the data file. Interpretation of the contents of the --- data file is determined by the contents of the corresponding control --- file. If a data file length has been specified, the next "Operand 1" --- octets over the same TCP connection are the intended contents of the --- data file. In this case, once all of the contents have been --- delivered, an octet of zero bits is sent as an indication that the --- file being sent is complete. A second level of acknowledgement --- processing must occur at this point. - - -local function send_hdr(con, control) - local sent = con.skt:send(control) - con.try(sent and sent >= 1 , "failed to send header file") - recv_ack(con) -end - -local function send_control(con, control) - local sent = con.skt:send(control) - con.try(sent and sent >= 1, "failed to send control file") - send_ack(con) -end - -local function send_data(con,fh,size) - local buf - while size > 0 do - buf,message = fh:read(8192) - if buf then - st = con.try(con.skt:send(buf)) - size = size - st - else - con.try(size == 0, "file size mismatch") - end - end - recv_ack(con) -- note the double acknowledgement - send_ack(con) - recv_ack(con) - return size -end - - ---[[ -local control_dflt = { - "H"..string.sub(socket.hostname,1,31).."\10", -- host - "C"..string.sub(socket.hostname,1,31).."\10", -- class - "J"..string.sub(filename,1,99).."\10", -- jobname - "L"..string.sub(user,1,31).."\10", -- print banner page - "I"..tonumber(indent).."\10", -- indent column count ('f' only) - "M"..string.sub(mail,1,128).."\10", -- mail when printed user@host - "N"..string.sub(filename,1,131).."\10", -- name of source file - "P"..string.sub(user,1,31).."\10", -- user name - "T"..string.sub(title,1,79).."\10", -- title for banner ('p' only) - "W"..tonumber(width or 132).."\10", -- width of print f,l,p only - - "f"..file.."\10", -- formatted print (remove control chars) - "l"..file.."\10", -- print - "o"..file.."\10", -- postscript - "p"..file.."\10", -- pr format - requires T, L - "r"..file.."\10", -- fortran format - "U"..file.."\10", -- Unlink (data file only) -} -]] - --- generate a varying job number -local seq = 0 -local function newjob(connection) - seq = seq + 1 - return math.floor(socket.gettime() * 1000 + seq)%1000 -end - - -local format_codes = { - binary = 'l', - text = 'f', - ps = 'o', - pr = 'p', - fortran = 'r', - l = 'l', - r = 'r', - o = 'o', - p = 'p', - f = 'f' -} - --- lp.send{option} --- requires option.file - -send = socket.protect(function(option) - socket.try(option and base.type(option) == "table", "invalid options") - local file = option.file - socket.try(file, "invalid file name") - local fh = socket.try(io.open(file,"rb")) - local datafile_size = fh:seek("end") -- get total size - fh:seek("set") -- go back to start of file - local localhost = socket.dns.gethostname() or os.getenv("COMPUTERNAME") - or "localhost" - local con = connect(localhost, option) --- format the control file - local jobno = newjob() - local localip = socket.dns.toip(localhost) - localhost = string.sub(localhost,1,31) - local user = string.sub(option.user or os.getenv("LPRUSER") or - os.getenv("USERNAME") or os.getenv("USER") or "anonymous", 1,31) - local lpfile = string.format("dfA%3.3d%-s", jobno, localhost); - local fmt = format_codes[option.format] or 'l' - local class = string.sub(option.class or localip or localhost,1,31) - local _,_,ctlfn = string.find(file,".*[%/%\\](.*)") - ctlfn = string.sub(ctlfn or file,1,131) - local cfile = - string.format("H%-s\nC%-s\nJ%-s\nP%-s\n%.1s%-s\nU%-s\nN%-s\n", - localhost, - class, - option.job or "LuaSocket", - user, - fmt, lpfile, - lpfile, - ctlfn); -- mandatory part of ctl file - if (option.banner) then cfile = cfile .. 'L'..user..'\10' end - if (option.indent) then cfile = cfile .. 'I'..base.tonumber(option.indent)..'\10' end - if (option.mail) then cfile = cfile .. 'M'..string.sub((option.mail),1,128)..'\10' end - if (fmt == 'p' and option.title) then cfile = cfile .. 'T'..string.sub((option.title),1,79)..'\10' end - if ((fmt == 'p' or fmt == 'l' or fmt == 'f') and option.width) then - cfile = cfile .. 'W'..base.tonumber(option,width)..'\10' - end - - con.skt:settimeout(option.timeout or 65) --- send the queue header - send_queue(con, option.queue) --- send the control file header - local cfilecmd = string.format("\2%d cfA%3.3d%-s\n",string.len(cfile), jobno, localhost); - send_hdr(con,cfilecmd) - --- send the control file - send_control(con,cfile) - --- send the data file header - local dfilecmd = string.format("\3%d dfA%3.3d%-s\n",datafile_size, jobno, localhost); - send_hdr(con,dfilecmd) - --- send the data file - send_data(con,fh,datafile_size) - fh:close() - con.skt:close(); - return jobno, datafile_size -end) - --- --- lp.query({host=,queue=printer|'*', format='l'|'s', list=}) --- -query = socket.protect(function(p) - p = p or {} - local localhost = socket.dns.gethostname() or os.getenv("COMPUTERNAME") - or "localhost" - local con = connect(localhost,p) - local fmt - if string.sub(p.format or 's',1,1) == 's' then fmt = 3 else fmt = 4 end - con.try(con.skt:send(string.format("%c%s %s\n", fmt, p.queue or "*", - p.list or ""))) - local data = con.try(con.skt:receive("*a")) - con.skt:close() - return data -end) diff --git a/etc/qp.lua b/etc/qp.lua deleted file mode 100644 index 523238b..0000000 --- a/etc/qp.lua +++ /dev/null @@ -1,23 +0,0 @@ ------------------------------------------------------------------------------ --- Little program to convert to and from Quoted-Printable --- LuaSocket sample files --- Author: Diego Nehab ------------------------------------------------------------------------------ -local ltn12 = require("ltn12") -local mime = require("mime") -local convert -arg = arg or {} -local mode = arg and arg[1] or "-et" -if mode == "-et" then - local normalize = mime.normalize() - local qp = mime.encode("quoted-printable") - local wrap = mime.wrap("quoted-printable") - convert = ltn12.filter.chain(normalize, qp, wrap) -elseif mode == "-eb" then - local qp = mime.encode("quoted-printable", "binary") - local wrap = mime.wrap("quoted-printable") - convert = ltn12.filter.chain(qp, wrap) -else convert = mime.decode("quoted-printable") end -local source = ltn12.source.chain(ltn12.source.file(io.stdin), convert) -local sink = ltn12.sink.file(io.stdout) -ltn12.pump.all(source, sink) diff --git a/etc/tftp.lua b/etc/tftp.lua deleted file mode 100644 index ed99cd1..0000000 --- a/etc/tftp.lua +++ /dev/null @@ -1,154 +0,0 @@ ------------------------------------------------------------------------------ --- TFTP support for the Lua language --- LuaSocket toolkit. --- Author: Diego Nehab ------------------------------------------------------------------------------ - ------------------------------------------------------------------------------ --- Load required files ------------------------------------------------------------------------------ -local base = _G -local table = require("table") -local math = require("math") -local string = require("string") -local socket = require("socket") -local ltn12 = require("ltn12") -local url = require("socket.url") -module("socket.tftp") - ------------------------------------------------------------------------------ --- Program constants ------------------------------------------------------------------------------ -local char = string.char -local byte = string.byte - -PORT = 69 -local OP_RRQ = 1 -local OP_WRQ = 2 -local OP_DATA = 3 -local OP_ACK = 4 -local OP_ERROR = 5 -local OP_INV = {"RRQ", "WRQ", "DATA", "ACK", "ERROR"} - ------------------------------------------------------------------------------ --- Packet creation functions ------------------------------------------------------------------------------ -local function RRQ(source, mode) - return char(0, OP_RRQ) .. source .. char(0) .. mode .. char(0) -end - -local function WRQ(source, mode) - return char(0, OP_RRQ) .. source .. char(0) .. mode .. char(0) -end - -local function ACK(block) - local low, high - low = math.mod(block, 256) - high = (block - low)/256 - return char(0, OP_ACK, high, low) -end - -local function get_OP(dgram) - local op = byte(dgram, 1)*256 + byte(dgram, 2) - return op -end - ------------------------------------------------------------------------------ --- Packet analysis functions ------------------------------------------------------------------------------ -local function split_DATA(dgram) - local block = byte(dgram, 3)*256 + byte(dgram, 4) - local data = string.sub(dgram, 5) - return block, data -end - -local function get_ERROR(dgram) - local code = byte(dgram, 3)*256 + byte(dgram, 4) - local msg - _,_, msg = string.find(dgram, "(.*)\000", 5) - return string.format("error code %d: %s", code, msg) -end - ------------------------------------------------------------------------------ --- The real work ------------------------------------------------------------------------------ -local function tget(gett) - local retries, dgram, sent, datahost, dataport, code - local last = 0 - socket.try(gett.host, "missing host") - local con = socket.try(socket.udp()) - local try = socket.newtry(function() con:close() end) - -- convert from name to ip if needed - gett.host = try(socket.dns.toip(gett.host)) - con:settimeout(1) - -- first packet gives data host/port to be used for data transfers - local path = string.gsub(gett.path or "", "^/", "") - path = url.unescape(path) - retries = 0 - repeat - sent = try(con:sendto(RRQ(path, "octet"), gett.host, gett.port)) - dgram, datahost, dataport = con:receivefrom() - retries = retries + 1 - until dgram or datahost ~= "timeout" or retries > 5 - try(dgram, datahost) - -- associate socket with data host/port - try(con:setpeername(datahost, dataport)) - -- default sink - local sink = gett.sink or ltn12.sink.null() - -- process all data packets - while 1 do - -- decode packet - code = get_OP(dgram) - try(code ~= OP_ERROR, get_ERROR(dgram)) - try(code == OP_DATA, "unhandled opcode " .. code) - -- get data packet parts - local block, data = split_DATA(dgram) - -- if not repeated, write - if block == last+1 then - try(sink(data)) - last = block - end - -- last packet brings less than 512 bytes of data - if string.len(data) < 512 then - try(con:send(ACK(block))) - try(con:close()) - try(sink(nil)) - return 1 - end - -- get the next packet - retries = 0 - repeat - sent = try(con:send(ACK(last))) - dgram, err = con:receive() - retries = retries + 1 - until dgram or err ~= "timeout" or retries > 5 - try(dgram, err) - end -end - -local default = { - port = PORT, - path ="/", - scheme = "tftp" -} - -local function parse(u) - local t = socket.try(url.parse(u, default)) - socket.try(t.scheme == "tftp", "invalid scheme '" .. t.scheme .. "'") - socket.try(t.host, "invalid host") - return t -end - -local function sget(u) - local gett = parse(u) - local t = {} - gett.sink = ltn12.sink.table(t) - tget(gett) - return table.concat(t) -end - -get = socket.protect(function(gett) - if base.type(gett) == "string" then return sget(gett) - else return tget(gett) end -end) - diff --git a/luasocket-scm-3.rockspec b/luasocket-scm-3.rockspec index 71f335c..f3d24e3 100644 --- a/luasocket-scm-3.rockspec +++ b/luasocket-scm-3.rockspec @@ -129,6 +129,5 @@ build = { copy_directories = { "docs" , "samples" - , "etc" , "test" } } diff --git a/makefile.dist b/makefile.dist index a27ba57..5ef44d3 100644 --- a/makefile.dist +++ b/makefile.dist @@ -22,20 +22,17 @@ SAMPLES = \ samples/lpr.lua \ samples/talker.lua \ samples/tinyirc.lua - -ETC = \ - etc/README \ - etc/b64.lua \ - etc/check-links.lua \ - etc/check-memory.lua \ - etc/dict.lua \ - etc/dispatch.lua \ - etc/eol.lua \ - etc/forward.lua \ - etc/get.lua \ - etc/lp.lua \ - etc/qp.lua \ - etc/tftp.lua + samples/b64.lua \ + samples/check-links.lua \ + samples/check-memory.lua \ + samples/dict.lua \ + samples/dispatch.lua \ + samples/eol.lua \ + samples/forward.lua \ + samples/get.lua \ + samples/lp.lua \ + samples/qp.lua \ + samples/tftp.lua SRC = \ src/makefile \ @@ -117,9 +114,6 @@ dist: cp -vf README.md $(DIST) cp -vf $(MAKE) $(DIST) - mkdir -p $(DIST)/etc - cp -vf $(ETC) $(DIST)/etc - mkdir -p $(DIST)/src cp -vf $(SRC) $(DIST)/src diff --git a/samples/README b/samples/README index e63a6f5..4ee06b6 100644 --- a/samples/README +++ b/samples/README @@ -1,11 +1,95 @@ This directory contains some sample programs using LuaSocket. This code is not supported. + tftp.lua -- Trivial FTP client + +This module implements file retrieval by the TFTP protocol. +Its main use was to test the UDP code, but since someone +found it usefull, I turned it into a module that is almost +official (no uploads, yet). + + dict.lua -- Dict client + +The dict.lua module started with a cool simple client +for the DICT protocol, written by Luiz Henrique Figueiredo. +This new version has been converted into a library, similar +to the HTTP and FTP libraries, that can be used from within +any luasocket application. Take a look on the source code +and you will be able to figure out how to use it. + + lp.lua -- LPD client library + +The lp.lua module implements the client part of the Line +Printer Daemon protocol, used to print files on Unix +machines. It is courtesy of David Burgess! See the source +code and the lpr.lua in the examples directory. + + b64.lua + qp.lua + eol.lua + +These are tiny programs that perform Base64, +Quoted-Printable and end-of-line marker conversions. + + get.lua -- file retriever + +This little program is a client that uses the FTP and +HTTP code to implement a command line file graber. Just +run + + lua get.lua <remote-file> [<local-file>] + +to download a remote file (either ftp:// or http://) to +the specified local file. The program also prints the +download throughput, elapsed time, bytes already downloaded +etc during download. + + check-memory.lua -- checks memory consumption + +This is just to see how much memory each module uses. + + dispatch.lua -- coroutine based dispatcher + +This is a first try at a coroutine based non-blocking +dispatcher for LuaSocket. Take a look at 'check-links.lua' +and at 'forward.lua' to see how to use it. + + check-links.lua -- HTML link checker program + +This little program scans a HTML file and checks for broken +links. It is similar to check-links.pl by Jamie Zawinski, +but uses all facilities of the LuaSocket library and the Lua +language. It has not been thoroughly tested, but it should +work. Just run + + lua check-links.lua [-n] {<url>} > output + +and open the result to see a list of broken links. Make sure +you check the '-n' switch. It runs in non-blocking mode, +using coroutines, and is MUCH faster! + + forward.lua -- coroutine based forward server + +This is a forward server that can accept several connections +and transfers simultaneously using non-blocking I/O and the +coroutine-based dispatcher. You can run, for example + + lua forward.lua 8080:proxy.com:3128 + +to redirect all local conections to port 8080 to the host +'proxy.com' at port 3128. + + unix.c and unix.h + +This is an implementation of Unix local domain sockets and +demonstrates how to extend LuaSocket with a new type of +transport. It has been tested on Linux and on Mac OS X. + listener.lua -- socket to stdout talker.lua -- stdin to socket listener.lua and talker.lua are about the simplest -applications you can write using LuaSocket. Run +applications you can write using LuaSocket. Run 'lua listener.lua' and 'lua talker.lua' @@ -17,13 +101,13 @@ be printed by listen.lua. This is a cool program written by David Burgess to print files using the Line Printer Daemon protocol, widely used in Unix machines. It uses the lp.lua implementation, in the -etc directory. Just run 'lua lpr.lua <filename> +samples directory. Just run 'lua lpr.lua <filename> queue=<printername>' and the file will print! cddb.lua -- CDDB client This is the first try on a simple CDDB client. Not really -useful, but one day it might become a module. +useful, but one day it might become a module. daytimeclnt.lua -- day time client diff --git a/samples/b64.lua b/samples/b64.lua new file mode 100644 index 0000000..11eeb2d --- /dev/null +++ b/samples/b64.lua @@ -0,0 +1,19 @@ +----------------------------------------------------------------------------- +-- Little program to convert to and from Base64 +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local ltn12 = require("ltn12") +local mime = require("mime") +local source = ltn12.source.file(io.stdin) +local sink = ltn12.sink.file(io.stdout) +local convert +if arg and arg[1] == '-d' then + convert = mime.decode("base64") +else + local base64 = mime.encode("base64") + local wrap = mime.wrap() + convert = ltn12.filter.chain(base64, wrap) +end +sink = ltn12.sink.chain(convert, sink) +ltn12.pump.all(source, sink) diff --git a/samples/check-links.lua b/samples/check-links.lua new file mode 100644 index 0000000..283f3ac --- /dev/null +++ b/samples/check-links.lua @@ -0,0 +1,111 @@ +----------------------------------------------------------------------------- +-- Little program that checks links in HTML files, using coroutines and +-- non-blocking I/O via the dispatcher module. +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local url = require("socket.url") +local dispatch = require("dispatch") +local http = require("socket.http") +dispatch.TIMEOUT = 10 + +-- make sure the user knows how to invoke us +arg = arg or {} +if #arg < 1 then + print("Usage:\n luasocket check-links.lua [-n] {<url>}") + exit() +end + +-- '-n' means we are running in non-blocking mode +if arg[1] == "-n" then + -- if non-blocking I/O was requested, use real dispatcher interface + table.remove(arg, 1) + handler = dispatch.newhandler("coroutine") +else + -- if using blocking I/O, use fake dispatcher interface + handler = dispatch.newhandler("sequential") +end + +local nthreads = 0 + +-- get the status of a URL using the dispatcher +function getstatus(link) + local parsed = url.parse(link, {scheme = "file"}) + if parsed.scheme == "http" then + nthreads = nthreads + 1 + handler:start(function() + local r, c, h, s = http.request{ + method = "HEAD", + url = link, + create = handler.tcp + } + if r and c == 200 then io.write('\t', link, '\n') + else io.write('\t', link, ': ', tostring(c), '\n') end + nthreads = nthreads - 1 + end) + end +end + +function readfile(path) + path = url.unescape(path) + local file, error = io.open(path, "r") + if file then + local body = file:read("*a") + file:close() + return body + else return nil, error end +end + +function load(u) + local parsed = url.parse(u, { scheme = "file" }) + local body, headers, code, error + local base = u + if parsed.scheme == "http" then + body, code, headers = http.request(u) + if code == 200 then + -- if there was a redirect, update base to reflect it + base = headers.location or base + end + if not body then + error = code + end + elseif parsed.scheme == "file" then + body, error = readfile(parsed.path) + else error = string.format("unhandled scheme '%s'", parsed.scheme) end + return base, body, error +end + +function getlinks(body, base) + -- get rid of comments + body = string.gsub(body, "%<%!%-%-.-%-%-%>", "") + local links = {} + -- extract links + body = string.gsub(body, '[Hh][Rr][Ee][Ff]%s*=%s*"([^"]*)"', function(href) + table.insert(links, url.absolute(base, href)) + end) + body = string.gsub(body, "[Hh][Rr][Ee][Ff]%s*=%s*'([^']*)'", function(href) + table.insert(links, url.absolute(base, href)) + end) + string.gsub(body, "[Hh][Rr][Ee][Ff]%s*=%s*(.-)>", function(href) + table.insert(links, url.absolute(base, href)) + end) + return links +end + +function checklinks(address) + local base, body, error = load(address) + if not body then print(error) return end + print("Checking ", base) + local links = getlinks(body, base) + for _, link in ipairs(links) do + getstatus(link) + end +end + +for _, address in ipairs(arg) do + checklinks(url.absolute("file:", address)) +end + +while nthreads > 0 do + handler:step() +end diff --git a/samples/check-memory.lua b/samples/check-memory.lua new file mode 100644 index 0000000..7bd984d --- /dev/null +++ b/samples/check-memory.lua @@ -0,0 +1,17 @@ +function load(s) + collectgarbage() + local a = gcinfo() + _G[s] = require(s) + collectgarbage() + local b = gcinfo() + print(s .. ":\t " .. (b-a) .. "k") +end + +load("socket.url") +load("ltn12") +load("socket") +load("mime") +load("socket.tp") +load("socket.smtp") +load("socket.http") +load("socket.ftp") diff --git a/samples/cookie.lua b/samples/cookie.lua new file mode 100644 index 0000000..fec10a1 --- /dev/null +++ b/samples/cookie.lua @@ -0,0 +1,88 @@ +local socket = require"socket" +local http = require"socket.http" +local url = require"socket.url" +local ltn12 = require"ltn12" + +local token_class = '[^%c%s%(%)%<%>%@%,%;%:%\\%"%/%[%]%?%=%{%}]' + +local function unquote(t, quoted) + local n = string.match(t, "%$(%d+)$") + if n then n = tonumber(n) end + if quoted[n] then return quoted[n] + else return t end +end + +local function parse_set_cookie(c, quoted, cookie_table) + c = c .. ";$last=last;" + local _, _, n, v, i = string.find(c, "(" .. token_class .. + "+)%s*=%s*(.-)%s*;%s*()") + local cookie = { + name = n, + value = unquote(v, quoted), + attributes = {} + } + while 1 do + _, _, n, v, i = string.find(c, "(" .. token_class .. + "+)%s*=?%s*(.-)%s*;%s*()", i) + if not n or n == "$last" then break end + cookie.attributes[#cookie.attributes+1] = { + name = n, + value = unquote(v, quoted) + } + end + cookie_table[#cookie_table+1] = cookie +end + +local function split_set_cookie(s, cookie_table) + cookie_table = cookie_table or {} + -- remove quoted strings from cookie list + local quoted = {} + s = string.gsub(s, '"(.-)"', function(q) + quoted[#quoted+1] = q + return "$" .. #quoted + end) + -- add sentinel + s = s .. ",$last=" + -- split into individual cookies + i = 1 + while 1 do + local _, _, cookie, next_token + _, _, cookie, i, next_token = string.find(s, "(.-)%s*%,%s*()(" .. + token_class .. "+)%s*=", i) + if not next_token then break end + parse_set_cookie(cookie, quoted, cookie_table) + if next_token == "$last" then break end + end + return cookie_table +end + +local function quote(s) + if string.find(s, "[ %,%;]") then return '"' .. s .. '"' + else return s end +end + +local _empty = {} +local function build_cookies(cookies) + s = "" + for i,v in ipairs(cookies or _empty) do + if v.name then + s = s .. v.name + if v.value and v.value ~= "" then + s = s .. '=' .. quote(v.value) + end + end + if v.name and #(v.attributes or _empty) > 0 then s = s .. "; " end + for j,u in ipairs(v.attributes or _empty) do + if u.name then + s = s .. u.name + if u.value and u.value ~= "" then + s = s .. '=' .. quote(u.value) + end + end + if j < #v.attributes then s = s .. "; " end + end + if i < #cookies then s = s .. ", " end + end + return s +end + diff --git a/samples/dict.lua b/samples/dict.lua new file mode 100644 index 0000000..8c5b711 --- /dev/null +++ b/samples/dict.lua @@ -0,0 +1,151 @@ +----------------------------------------------------------------------------- +-- Little program to download DICT word definitions +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- + +----------------------------------------------------------------------------- +-- Load required modules +----------------------------------------------------------------------------- +local base = _G +local string = require("string") +local table = require("table") +local socket = require("socket") +local url = require("socket.url") +local tp = require("socket.tp") +module("socket.dict") + +----------------------------------------------------------------------------- +-- Globals +----------------------------------------------------------------------------- +HOST = "dict.org" +PORT = 2628 +TIMEOUT = 10 + +----------------------------------------------------------------------------- +-- Low-level dict API +----------------------------------------------------------------------------- +local metat = { __index = {} } + +function open(host, port) + local tp = socket.try(tp.connect(host or HOST, port or PORT, TIMEOUT)) + return base.setmetatable({tp = tp}, metat) +end + +function metat.__index:greet() + return socket.try(self.tp:check(220)) +end + +function metat.__index:check(ok) + local code, status = socket.try(self.tp:check(ok)) + return code, + base.tonumber(socket.skip(2, string.find(status, "^%d%d%d (%d*)"))) +end + +function metat.__index:getdef() + local line = socket.try(self.tp:receive()) + local def = {} + while line ~= "." do + table.insert(def, line) + line = socket.try(self.tp:receive()) + end + return table.concat(def, "\n") +end + +function metat.__index:define(database, word) + database = database or "!" + socket.try(self.tp:command("DEFINE", database .. " " .. word)) + local code, count = self:check(150) + local defs = {} + for i = 1, count do + self:check(151) + table.insert(defs, self:getdef()) + end + self:check(250) + return defs +end + +function metat.__index:match(database, strat, word) + database = database or "!" + strat = strat or "." + socket.try(self.tp:command("MATCH", database .." ".. strat .." ".. word)) + self:check(152) + local mat = {} + local line = socket.try(self.tp:receive()) + while line ~= '.' do + database, word = socket.skip(2, string.find(line, "(%S+) (.*)")) + if not mat[database] then mat[database] = {} end + table.insert(mat[database], word) + line = socket.try(self.tp:receive()) + end + self:check(250) + return mat +end + +function metat.__index:quit() + self.tp:command("QUIT") + return self:check(221) +end + +function metat.__index:close() + return self.tp:close() +end + +----------------------------------------------------------------------------- +-- High-level dict API +----------------------------------------------------------------------------- +local default = { + scheme = "dict", + host = "dict.org" +} + +local function there(f) + if f == "" then return nil + else return f end +end + +local function parse(u) + local t = socket.try(url.parse(u, default)) + socket.try(t.scheme == "dict", "invalid scheme '" .. t.scheme .. "'") + socket.try(t.path, "invalid path in url") + local cmd, arg = socket.skip(2, string.find(t.path, "^/(.)(.*)$")) + socket.try(cmd == "d" or cmd == "m", "<command> should be 'm' or 'd'") + socket.try(arg and arg ~= "", "need at least <word> in URL") + t.command, t.argument = cmd, arg + arg = string.gsub(arg, "^:([^:]+)", function(f) t.word = f end) + socket.try(t.word, "need at least <word> in URL") + arg = string.gsub(arg, "^:([^:]*)", function(f) t.database = there(f) end) + if cmd == "m" then + arg = string.gsub(arg, "^:([^:]*)", function(f) t.strat = there(f) end) + end + string.gsub(arg, ":([^:]*)$", function(f) t.n = base.tonumber(f) end) + return t +end + +local function tget(gett) + local con = open(gett.host, gett.port) + con:greet() + if gett.command == "d" then + local def = con:define(gett.database, gett.word) + con:quit() + con:close() + if gett.n then return def[gett.n] + else return def end + elseif gett.command == "m" then + local mat = con:match(gett.database, gett.strat, gett.word) + con:quit() + con:close() + return mat + else return nil, "invalid command" end +end + +local function sget(u) + local gett = parse(u) + return tget(gett) +end + +get = socket.protect(function(gett) + if base.type(gett) == "string" then return sget(gett) + else return tget(gett) end +end) + diff --git a/samples/dispatch.lua b/samples/dispatch.lua new file mode 100644 index 0000000..2485415 --- /dev/null +++ b/samples/dispatch.lua @@ -0,0 +1,307 @@ +----------------------------------------------------------------------------- +-- A hacked dispatcher module +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local base = _G +local table = require("table") +local string = require("string") +local socket = require("socket") +local coroutine = require("coroutine") +module("dispatch") + +-- if too much time goes by without any activity in one of our sockets, we +-- just kill it +TIMEOUT = 60 + +----------------------------------------------------------------------------- +-- We implement 3 types of dispatchers: +-- sequential +-- coroutine +-- threaded +-- The user can choose whatever one is needed +----------------------------------------------------------------------------- +local handlert = {} + +-- default handler is coroutine +function newhandler(mode) + mode = mode or "coroutine" + return handlert[mode]() +end + +local function seqstart(self, func) + return func() +end + +-- sequential handler simply calls the functions and doesn't wrap I/O +function handlert.sequential() + return { + tcp = socket.tcp, + start = seqstart + } +end + +----------------------------------------------------------------------------- +-- Mega hack. Don't try to do this at home. +----------------------------------------------------------------------------- +-- we can't yield across calls to protect on Lua 5.1, so we rewrite it with +-- coroutines +-- make sure you don't require any module that uses socket.protect before +-- loading our hack +if string.sub(base._VERSION, -3) == "5.1" then + local function _protect(co, status, ...) + if not status then + local msg = ... + if base.type(msg) == 'table' then + return nil, msg[1] + else + base.error(msg, 0) + end + end + if coroutine.status(co) == "suspended" then + return _protect(co, coroutine.resume(co, coroutine.yield(...))) + else + return ... + end + end + + function socket.protect(f) + return function(...) + local co = coroutine.create(f) + return _protect(co, coroutine.resume(co, ...)) + end + end +end + +----------------------------------------------------------------------------- +-- Simple set data structure. O(1) everything. +----------------------------------------------------------------------------- +local function newset() + local reverse = {} + local set = {} + return base.setmetatable(set, {__index = { + insert = function(set, value) + if not reverse[value] then + table.insert(set, value) + reverse[value] = #set + end + end, + remove = function(set, value) + local index = reverse[value] + if index then + reverse[value] = nil + local top = table.remove(set) + if top ~= value then + reverse[top] = index + set[index] = top + end + end + end + }}) +end + +----------------------------------------------------------------------------- +-- socket.tcp() wrapper for the coroutine dispatcher +----------------------------------------------------------------------------- +local function cowrap(dispatcher, tcp, error) + if not tcp then return nil, error end + -- put it in non-blocking mode right away + tcp:settimeout(0) + -- metatable for wrap produces new methods on demand for those that we + -- don't override explicitly. + local metat = { __index = function(table, key) + table[key] = function(...) + return tcp[key](tcp,select(2,...)) + end + return table[key] + end} + -- does our user want to do his own non-blocking I/O? + local zero = false + -- create a wrap object that will behave just like a real socket object + local wrap = { } + -- we ignore settimeout to preserve our 0 timeout, but record whether + -- the user wants to do his own non-blocking I/O + function wrap:settimeout(value, mode) + if value == 0 then zero = true + else zero = false end + return 1 + end + -- send in non-blocking mode and yield on timeout + function wrap:send(data, first, last) + first = (first or 1) - 1 + local result, error + while true do + -- return control to dispatcher and tell it we want to send + -- if upon return the dispatcher tells us we timed out, + -- return an error to whoever called us + if coroutine.yield(dispatcher.sending, tcp) == "timeout" then + return nil, "timeout" + end + -- try sending + result, error, first = tcp:send(data, first+1, last) + -- if we are done, or there was an unexpected error, + -- break away from loop + if error ~= "timeout" then return result, error, first end + end + end + -- receive in non-blocking mode and yield on timeout + -- or simply return partial read, if user requested timeout = 0 + function wrap:receive(pattern, partial) + local error = "timeout" + local value + while true do + -- return control to dispatcher and tell it we want to receive + -- if upon return the dispatcher tells us we timed out, + -- return an error to whoever called us + if coroutine.yield(dispatcher.receiving, tcp) == "timeout" then + return nil, "timeout" + end + -- try receiving + value, error, partial = tcp:receive(pattern, partial) + -- if we are done, or there was an unexpected error, + -- break away from loop. also, if the user requested + -- zero timeout, return all we got + if (error ~= "timeout") or zero then + return value, error, partial + end + end + end + -- connect in non-blocking mode and yield on timeout + function wrap:connect(host, port) + local result, error = tcp:connect(host, port) + if error == "timeout" then + -- return control to dispatcher. we will be writable when + -- connection succeeds. + -- if upon return the dispatcher tells us we have a + -- timeout, just abort + if coroutine.yield(dispatcher.sending, tcp) == "timeout" then + return nil, "timeout" + end + -- when we come back, check if connection was successful + result, error = tcp:connect(host, port) + if result or error == "already connected" then return 1 + else return nil, "non-blocking connect failed" end + else return result, error end + end + -- accept in non-blocking mode and yield on timeout + function wrap:accept() + while 1 do + -- return control to dispatcher. we will be readable when a + -- connection arrives. + -- if upon return the dispatcher tells us we have a + -- timeout, just abort + if coroutine.yield(dispatcher.receiving, tcp) == "timeout" then + return nil, "timeout" + end + local client, error = tcp:accept() + if error ~= "timeout" then + return cowrap(dispatcher, client, error) + end + end + end + -- remove cortn from context + function wrap:close() + dispatcher.stamp[tcp] = nil + dispatcher.sending.set:remove(tcp) + dispatcher.sending.cortn[tcp] = nil + dispatcher.receiving.set:remove(tcp) + dispatcher.receiving.cortn[tcp] = nil + return tcp:close() + end + return base.setmetatable(wrap, metat) +end + + +----------------------------------------------------------------------------- +-- Our coroutine dispatcher +----------------------------------------------------------------------------- +local cometat = { __index = {} } + +function schedule(cortn, status, operation, tcp) + if status then + if cortn and operation then + operation.set:insert(tcp) + operation.cortn[tcp] = cortn + operation.stamp[tcp] = socket.gettime() + end + else base.error(operation) end +end + +function kick(operation, tcp) + operation.cortn[tcp] = nil + operation.set:remove(tcp) +end + +function wakeup(operation, tcp) + local cortn = operation.cortn[tcp] + -- if cortn is still valid, wake it up + if cortn then + kick(operation, tcp) + return cortn, coroutine.resume(cortn) + -- othrewise, just get scheduler not to do anything + else + return nil, true + end +end + +function abort(operation, tcp) + local cortn = operation.cortn[tcp] + if cortn then + kick(operation, tcp) + coroutine.resume(cortn, "timeout") + end +end + +-- step through all active cortns +function cometat.__index:step() + -- check which sockets are interesting and act on them + local readable, writable = socket.select(self.receiving.set, + self.sending.set, 1) + -- for all readable connections, resume their cortns and reschedule + -- when they yield back to us + for _, tcp in base.ipairs(readable) do + schedule(wakeup(self.receiving, tcp)) + end + -- for all writable connections, do the same + for _, tcp in base.ipairs(writable) do + schedule(wakeup(self.sending, tcp)) + end + -- politely ask replacement I/O functions in idle cortns to + -- return reporting a timeout + local now = socket.gettime() + for tcp, stamp in base.pairs(self.stamp) do + if tcp.class == "tcp{client}" and now - stamp > TIMEOUT then + abort(self.sending, tcp) + abort(self.receiving, tcp) + end + end +end + +function cometat.__index:start(func) + local cortn = coroutine.create(func) + schedule(cortn, coroutine.resume(cortn)) +end + +function handlert.coroutine() + local stamp = {} + local dispatcher = { + stamp = stamp, + sending = { + name = "sending", + set = newset(), + cortn = {}, + stamp = stamp + }, + receiving = { + name = "receiving", + set = newset(), + cortn = {}, + stamp = stamp + }, + } + function dispatcher.tcp() + return cowrap(dispatcher, socket.tcp()) + end + return base.setmetatable(dispatcher, cometat) +end + diff --git a/samples/eol.lua b/samples/eol.lua new file mode 100644 index 0000000..eeaf0ce --- /dev/null +++ b/samples/eol.lua @@ -0,0 +1,13 @@ +----------------------------------------------------------------------------- +-- Little program to adjust end of line markers. +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local mime = require("mime") +local ltn12 = require("ltn12") +local marker = '\n' +if arg and arg[1] == '-d' then marker = '\r\n' end +local filter = mime.normalize(marker) +local source = ltn12.source.chain(ltn12.source.file(io.stdin), filter) +local sink = ltn12.sink.file(io.stdout) +ltn12.pump.all(source, sink) diff --git a/samples/forward.lua b/samples/forward.lua new file mode 100644 index 0000000..05ced1a --- /dev/null +++ b/samples/forward.lua @@ -0,0 +1,65 @@ +-- load our favourite library +local dispatch = require("dispatch") +local handler = dispatch.newhandler() + +-- make sure the user knows how to invoke us +if #arg < 1 then + print("Usage") + print(" lua forward.lua <iport:ohost:oport> ...") + os.exit(1) +end + +-- function to move data from one socket to the other +local function move(foo, bar) + local live + while 1 do + local data, error, partial = foo:receive(2048) + live = data or error == "timeout" + data = data or partial + local result, error = bar:send(data) + if not live or not result then + foo:close() + bar:close() + break + end + end +end + +-- for each tunnel, start a new server +for i, v in ipairs(arg) do + -- capture forwarding parameters + local _, _, iport, ohost, oport = string.find(v, "([^:]+):([^:]+):([^:]+)") + assert(iport, "invalid arguments") + -- create our server socket + local server = assert(handler.tcp()) + assert(server:setoption("reuseaddr", true)) + assert(server:bind("*", iport)) + assert(server:listen(32)) + -- handler for the server object loops accepting new connections + handler:start(function() + while 1 do + local client = assert(server:accept()) + assert(client:settimeout(0)) + -- for each new connection, start a new client handler + handler:start(function() + -- handler tries to connect to peer + local peer = assert(handler.tcp()) + assert(peer:settimeout(0)) + assert(peer:connect(ohost, oport)) + -- if sucessful, starts a new handler to send data from + -- client to peer + handler:start(function() + move(client, peer) + end) + -- afte starting new handler, enter in loop sending data from + -- peer to client + move(peer, client) + end) + end + end) +end + +-- simply loop stepping the server +while 1 do + handler:step() +end diff --git a/samples/get.lua b/samples/get.lua new file mode 100644 index 0000000..d53c465 --- /dev/null +++ b/samples/get.lua @@ -0,0 +1,141 @@ +----------------------------------------------------------------------------- +-- Little program to download files from URLs +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local socket = require("socket") +local http = require("socket.http") +local ftp = require("socket.ftp") +local url = require("socket.url") +local ltn12 = require("ltn12") + +-- formats a number of seconds into human readable form +function nicetime(s) + local l = "s" + if s > 60 then + s = s / 60 + l = "m" + if s > 60 then + s = s / 60 + l = "h" + if s > 24 then + s = s / 24 + l = "d" -- hmmm + end + end + end + if l == "s" then return string.format("%5.0f%s", s, l) + else return string.format("%5.2f%s", s, l) end +end + +-- formats a number of bytes into human readable form +function nicesize(b) + local l = "B" + if b > 1024 then + b = b / 1024 + l = "KB" + if b > 1024 then + b = b / 1024 + l = "MB" + if b > 1024 then + b = b / 1024 + l = "GB" -- hmmm + end + end + end + return string.format("%7.2f%2s", b, l) +end + +-- returns a string with the current state of the download +local remaining_s = "%s received, %s/s throughput, %2.0f%% done, %s remaining" +local elapsed_s = "%s received, %s/s throughput, %s elapsed " +function gauge(got, delta, size) + local rate = got / delta + if size and size >= 1 then + return string.format(remaining_s, nicesize(got), nicesize(rate), + 100*got/size, nicetime((size-got)/rate)) + else + return string.format(elapsed_s, nicesize(got), + nicesize(rate), nicetime(delta)) + end +end + +-- creates a new instance of a receive_cb that saves to disk +-- kind of copied from luasocket's manual callback examples +function stats(size) + local start = socket.gettime() + local last = start + local got = 0 + return function(chunk) + -- elapsed time since start + local current = socket.gettime() + if chunk then + -- total bytes received + got = got + string.len(chunk) + -- not enough time for estimate + if current - last > 1 then + io.stderr:write("\r", gauge(got, current - start, size)) + io.stderr:flush() + last = current + end + else + -- close up + io.stderr:write("\r", gauge(got, current - start), "\n") + end + return chunk + end +end + +-- determines the size of a http file +function gethttpsize(u) + local r, c, h = http.request {method = "HEAD", url = u} + if c == 200 then + return tonumber(h["content-length"]) + end +end + +-- downloads a file using the http protocol +function getbyhttp(u, file) + local save = ltn12.sink.file(file or io.stdout) + -- only print feedback if output is not stdout + if file then save = ltn12.sink.chain(stats(gethttpsize(u)), save) end + local r, c, h, s = http.request {url = u, sink = save } + if c ~= 200 then io.stderr:write(s or c, "\n") end +end + +-- downloads a file using the ftp protocol +function getbyftp(u, file) + local save = ltn12.sink.file(file or io.stdout) + -- only print feedback if output is not stdout + -- and we don't know how big the file is + if file then save = ltn12.sink.chain(stats(), save) end + local gett = url.parse(u) + gett.sink = save + gett.type = "i" + local ret, err = ftp.get(gett) + if err then print(err) end +end + +-- determines the scheme +function getscheme(u) + -- this is an heuristic to solve a common invalid url poblem + if not string.find(u, "//") then u = "//" .. u end + local parsed = url.parse(u, {scheme = "http"}) + return parsed.scheme +end + +-- gets a file either by http or ftp, saving as <name> +function get(u, name) + local fout = name and io.open(name, "wb") + local scheme = getscheme(u) + if scheme == "ftp" then getbyftp(u, fout) + elseif scheme == "http" then getbyhttp(u, fout) + else print("unknown scheme" .. scheme) end +end + +-- main program +arg = arg or {} +if #arg < 1 then + io.write("Usage:\n lua get.lua <remote-url> [<local-file>]\n") + os.exit(1) +else get(arg[1], arg[2]) end diff --git a/samples/links b/samples/links new file mode 100644 index 0000000..087f1c0 --- /dev/null +++ b/samples/links @@ -0,0 +1,17 @@ +<a href="http://www.cs.princeton.edu"> bla </a> +<a href="http://www.princeton.edu"> bla </a> +<a href="http://www.tecgraf.puc-rio.br"> bla </a> +<a href="http://www.inf.puc-rio.br"> bla </a> +<a href="http://www.puc-rio.br"> bla </a> +<a href="http://www.impa.br"> bla </a> +<a href="http://www.lua.org"> bla </a> +<a href="http://www.lua-users.org"> bla </a> +<a href="http://www.amazon.com"> bla </a> +<a href="http://www.google.com"> bla </a> +<a href="http://www.nytimes.com"> bla </a> +<a href="http://www.bbc.co.uk"> bla </a> +<a href="http://oglobo.globo.com"> bla </a> +<a href="http://slate.msn.com"> bla </a> +<a href="http://www.apple.com"> bla </a> +<a href="http://www.microsoft.com"> bla </a> +<a href="http://www.nasa.gov"> bla </a> diff --git a/samples/lp.lua b/samples/lp.lua new file mode 100644 index 0000000..25f0b95 --- /dev/null +++ b/samples/lp.lua @@ -0,0 +1,323 @@ +----------------------------------------------------------------------------- +-- LPD support for the Lua language +-- LuaSocket toolkit. +-- Author: David Burgess +-- Modified by Diego Nehab, but David is in charge +----------------------------------------------------------------------------- +--[[ + if you have any questions: RFC 1179 +]] +-- make sure LuaSocket is loaded +local io = require("io") +local base = _G +local os = require("os") +local math = require("math") +local string = require("string") +local socket = require("socket") +local ltn12 = require("ltn12") +module("socket.lp") + +-- default port +PORT = 515 +SERVER = os.getenv("SERVER_NAME") or os.getenv("COMPUTERNAME") or "localhost" +PRINTER = os.getenv("PRINTER") or "printer" + +local function connect(localhost, option) + local host = option.host or SERVER + local port = option.port or PORT + local skt + local try = socket.newtry(function() if skt then skt:close() end end) + if option.localbind then + -- bind to a local port (if we can) + local localport = 721 + local done, err + repeat + skt = socket.try(socket.tcp()) + try(skt:settimeout(30)) + done, err = skt:bind(localhost, localport) + if not done then + localport = localport + 1 + skt:close() + skt = nil + else break end + until localport > 731 + socket.try(skt, err) + else skt = socket.try(socket.tcp()) end + try(skt:connect(host, port)) + return { skt = skt, try = try } +end + +--[[ +RFC 1179 +5.3 03 - Send queue state (short) + + +----+-------+----+------+----+ + | 03 | Queue | SP | List | LF | + +----+-------+----+------+----+ + Command code - 3 + Operand 1 - Printer queue name + Other operands - User names or job numbers + + If the user names or job numbers or both are supplied then only those + jobs for those users or with those numbers will be sent. + + The response is an ASCII stream which describes the printer queue. + The stream continues until the connection closes. Ends of lines are + indicated with ASCII LF control characters. The lines may also + contain ASCII HT control characters. + +5.4 04 - Send queue state (long) + + +----+-------+----+------+----+ + | 04 | Queue | SP | List | LF | + +----+-------+----+------+----+ + Command code - 4 + Operand 1 - Printer queue name + Other operands - User names or job numbers + + If the user names or job numbers or both are supplied then only those + jobs for those users or with those numbers will be sent. + + The response is an ASCII stream which describes the printer queue. + The stream continues until the connection closes. Ends of lines are + indicated with ASCII LF control characters. The lines may also + contain ASCII HT control characters. +]] + +-- gets server acknowledement +local function recv_ack(con) + local ack = con.skt:receive(1) + con.try(string.char(0) == ack, "failed to receive server acknowledgement") +end + +-- sends client acknowledement +local function send_ack(con) + local sent = con.skt:send(string.char(0)) + con.try(sent == 1, "failed to send acknowledgement") +end + +-- sends queue request +-- 5.2 02 - Receive a printer job +-- +-- +----+-------+----+ +-- | 02 | Queue | LF | +-- +----+-------+----+ +-- Command code - 2 +-- Operand - Printer queue name +-- +-- Receiving a job is controlled by a second level of commands. The +-- daemon is given commands by sending them over the same connection. +-- The commands are described in the next section (6). +-- +-- After this command is sent, the client must read an acknowledgement +-- octet from the daemon. A positive acknowledgement is an octet of +-- zero bits. A negative acknowledgement is an octet of any other +-- pattern. +local function send_queue(con, queue) + queue = queue or PRINTER + local str = string.format("\2%s\10", queue) + local sent = con.skt:send(str) + con.try(sent == string.len(str), "failed to send print request") + recv_ack(con) +end + +-- sends control file +-- 6.2 02 - Receive control file +-- +-- +----+-------+----+------+----+ +-- | 02 | Count | SP | Name | LF | +-- +----+-------+----+------+----+ +-- Command code - 2 +-- Operand 1 - Number of bytes in control file +-- Operand 2 - Name of control file +-- +-- The control file must be an ASCII stream with the ends of lines +-- indicated by ASCII LF. The total number of bytes in the stream is +-- sent as the first operand. The name of the control file is sent as +-- the second. It should start with ASCII "cfA", followed by a three +-- digit job number, followed by the host name which has constructed the +-- control file. Acknowledgement processing must occur as usual after +-- the command is sent. +-- +-- The next "Operand 1" octets over the same TCP connection are the +-- intended contents of the control file. Once all of the contents have +-- been delivered, an octet of zero bits is sent as an indication that +-- the file being sent is complete. A second level of acknowledgement +-- processing must occur at this point. + +-- sends data file +-- 6.3 03 - Receive data file +-- +-- +----+-------+----+------+----+ +-- | 03 | Count | SP | Name | LF | +-- +----+-------+----+------+----+ +-- Command code - 3 +-- Operand 1 - Number of bytes in data file +-- Operand 2 - Name of data file +-- +-- The data file may contain any 8 bit values at all. The total number +-- of bytes in the stream may be sent as the first operand, otherwise +-- the field should be cleared to 0. The name of the data file should +-- start with ASCII "dfA". This should be followed by a three digit job +-- number. The job number should be followed by the host name which has +-- constructed the data file. Interpretation of the contents of the +-- data file is determined by the contents of the corresponding control +-- file. If a data file length has been specified, the next "Operand 1" +-- octets over the same TCP connection are the intended contents of the +-- data file. In this case, once all of the contents have been +-- delivered, an octet of zero bits is sent as an indication that the +-- file being sent is complete. A second level of acknowledgement +-- processing must occur at this point. + + +local function send_hdr(con, control) + local sent = con.skt:send(control) + con.try(sent and sent >= 1 , "failed to send header file") + recv_ack(con) +end + +local function send_control(con, control) + local sent = con.skt:send(control) + con.try(sent and sent >= 1, "failed to send control file") + send_ack(con) +end + +local function send_data(con,fh,size) + local buf + while size > 0 do + buf,message = fh:read(8192) + if buf then + st = con.try(con.skt:send(buf)) + size = size - st + else + con.try(size == 0, "file size mismatch") + end + end + recv_ack(con) -- note the double acknowledgement + send_ack(con) + recv_ack(con) + return size +end + + +--[[ +local control_dflt = { + "H"..string.sub(socket.hostname,1,31).."\10", -- host + "C"..string.sub(socket.hostname,1,31).."\10", -- class + "J"..string.sub(filename,1,99).."\10", -- jobname + "L"..string.sub(user,1,31).."\10", -- print banner page + "I"..tonumber(indent).."\10", -- indent column count ('f' only) + "M"..string.sub(mail,1,128).."\10", -- mail when printed user@host + "N"..string.sub(filename,1,131).."\10", -- name of source file + "P"..string.sub(user,1,31).."\10", -- user name + "T"..string.sub(title,1,79).."\10", -- title for banner ('p' only) + "W"..tonumber(width or 132).."\10", -- width of print f,l,p only + + "f"..file.."\10", -- formatted print (remove control chars) + "l"..file.."\10", -- print + "o"..file.."\10", -- postscript + "p"..file.."\10", -- pr format - requires T, L + "r"..file.."\10", -- fortran format + "U"..file.."\10", -- Unlink (data file only) +} +]] + +-- generate a varying job number +local seq = 0 +local function newjob(connection) + seq = seq + 1 + return math.floor(socket.gettime() * 1000 + seq)%1000 +end + + +local format_codes = { + binary = 'l', + text = 'f', + ps = 'o', + pr = 'p', + fortran = 'r', + l = 'l', + r = 'r', + o = 'o', + p = 'p', + f = 'f' +} + +-- lp.send{option} +-- requires option.file + +send = socket.protect(function(option) + socket.try(option and base.type(option) == "table", "invalid options") + local file = option.file + socket.try(file, "invalid file name") + local fh = socket.try(io.open(file,"rb")) + local datafile_size = fh:seek("end") -- get total size + fh:seek("set") -- go back to start of file + local localhost = socket.dns.gethostname() or os.getenv("COMPUTERNAME") + or "localhost" + local con = connect(localhost, option) +-- format the control file + local jobno = newjob() + local localip = socket.dns.toip(localhost) + localhost = string.sub(localhost,1,31) + local user = string.sub(option.user or os.getenv("LPRUSER") or + os.getenv("USERNAME") or os.getenv("USER") or "anonymous", 1,31) + local lpfile = string.format("dfA%3.3d%-s", jobno, localhost); + local fmt = format_codes[option.format] or 'l' + local class = string.sub(option.class or localip or localhost,1,31) + local _,_,ctlfn = string.find(file,".*[%/%\\](.*)") + ctlfn = string.sub(ctlfn or file,1,131) + local cfile = + string.format("H%-s\nC%-s\nJ%-s\nP%-s\n%.1s%-s\nU%-s\nN%-s\n", + localhost, + class, + option.job or "LuaSocket", + user, + fmt, lpfile, + lpfile, + ctlfn); -- mandatory part of ctl file + if (option.banner) then cfile = cfile .. 'L'..user..'\10' end + if (option.indent) then cfile = cfile .. 'I'..base.tonumber(option.indent)..'\10' end + if (option.mail) then cfile = cfile .. 'M'..string.sub((option.mail),1,128)..'\10' end + if (fmt == 'p' and option.title) then cfile = cfile .. 'T'..string.sub((option.title),1,79)..'\10' end + if ((fmt == 'p' or fmt == 'l' or fmt == 'f') and option.width) then + cfile = cfile .. 'W'..base.tonumber(option,width)..'\10' + end + + con.skt:settimeout(option.timeout or 65) +-- send the queue header + send_queue(con, option.queue) +-- send the control file header + local cfilecmd = string.format("\2%d cfA%3.3d%-s\n",string.len(cfile), jobno, localhost); + send_hdr(con,cfilecmd) + +-- send the control file + send_control(con,cfile) + +-- send the data file header + local dfilecmd = string.format("\3%d dfA%3.3d%-s\n",datafile_size, jobno, localhost); + send_hdr(con,dfilecmd) + +-- send the data file + send_data(con,fh,datafile_size) + fh:close() + con.skt:close(); + return jobno, datafile_size +end) + +-- +-- lp.query({host=,queue=printer|'*', format='l'|'s', list=}) +-- +query = socket.protect(function(p) + p = p or {} + local localhost = socket.dns.gethostname() or os.getenv("COMPUTERNAME") + or "localhost" + local con = connect(localhost,p) + local fmt + if string.sub(p.format or 's',1,1) == 's' then fmt = 3 else fmt = 4 end + con.try(con.skt:send(string.format("%c%s %s\n", fmt, p.queue or "*", + p.list or ""))) + local data = con.try(con.skt:receive("*a")) + con.skt:close() + return data +end) diff --git a/samples/qp.lua b/samples/qp.lua new file mode 100644 index 0000000..523238b --- /dev/null +++ b/samples/qp.lua @@ -0,0 +1,23 @@ +----------------------------------------------------------------------------- +-- Little program to convert to and from Quoted-Printable +-- LuaSocket sample files +-- Author: Diego Nehab +----------------------------------------------------------------------------- +local ltn12 = require("ltn12") +local mime = require("mime") +local convert +arg = arg or {} +local mode = arg and arg[1] or "-et" +if mode == "-et" then + local normalize = mime.normalize() + local qp = mime.encode("quoted-printable") + local wrap = mime.wrap("quoted-printable") + convert = ltn12.filter.chain(normalize, qp, wrap) +elseif mode == "-eb" then + local qp = mime.encode("quoted-printable", "binary") + local wrap = mime.wrap("quoted-printable") + convert = ltn12.filter.chain(qp, wrap) +else convert = mime.decode("quoted-printable") end +local source = ltn12.source.chain(ltn12.source.file(io.stdin), convert) +local sink = ltn12.sink.file(io.stdout) +ltn12.pump.all(source, sink) diff --git a/samples/tftp.lua b/samples/tftp.lua new file mode 100644 index 0000000..ed99cd1 --- /dev/null +++ b/samples/tftp.lua @@ -0,0 +1,154 @@ +----------------------------------------------------------------------------- +-- TFTP support for the Lua language +-- LuaSocket toolkit. +-- Author: Diego Nehab +----------------------------------------------------------------------------- + +----------------------------------------------------------------------------- +-- Load required files +----------------------------------------------------------------------------- +local base = _G +local table = require("table") +local math = require("math") +local string = require("string") +local socket = require("socket") +local ltn12 = require("ltn12") +local url = require("socket.url") +module("socket.tftp") + +----------------------------------------------------------------------------- +-- Program constants +----------------------------------------------------------------------------- +local char = string.char +local byte = string.byte + +PORT = 69 +local OP_RRQ = 1 +local OP_WRQ = 2 +local OP_DATA = 3 +local OP_ACK = 4 +local OP_ERROR = 5 +local OP_INV = {"RRQ", "WRQ", "DATA", "ACK", "ERROR"} + +----------------------------------------------------------------------------- +-- Packet creation functions +----------------------------------------------------------------------------- +local function RRQ(source, mode) + return char(0, OP_RRQ) .. source .. char(0) .. mode .. char(0) +end + +local function WRQ(source, mode) + return char(0, OP_RRQ) .. source .. char(0) .. mode .. char(0) +end + +local function ACK(block) + local low, high + low = math.mod(block, 256) + high = (block - low)/256 + return char(0, OP_ACK, high, low) +end + +local function get_OP(dgram) + local op = byte(dgram, 1)*256 + byte(dgram, 2) + return op +end + +----------------------------------------------------------------------------- +-- Packet analysis functions +----------------------------------------------------------------------------- +local function split_DATA(dgram) + local block = byte(dgram, 3)*256 + byte(dgram, 4) + local data = string.sub(dgram, 5) + return block, data +end + +local function get_ERROR(dgram) + local code = byte(dgram, 3)*256 + byte(dgram, 4) + local msg + _,_, msg = string.find(dgram, "(.*)\000", 5) + return string.format("error code %d: %s", code, msg) +end + +----------------------------------------------------------------------------- +-- The real work +----------------------------------------------------------------------------- +local function tget(gett) + local retries, dgram, sent, datahost, dataport, code + local last = 0 + socket.try(gett.host, "missing host") + local con = socket.try(socket.udp()) + local try = socket.newtry(function() con:close() end) + -- convert from name to ip if needed + gett.host = try(socket.dns.toip(gett.host)) + con:settimeout(1) + -- first packet gives data host/port to be used for data transfers + local path = string.gsub(gett.path or "", "^/", "") + path = url.unescape(path) + retries = 0 + repeat + sent = try(con:sendto(RRQ(path, "octet"), gett.host, gett.port)) + dgram, datahost, dataport = con:receivefrom() + retries = retries + 1 + until dgram or datahost ~= "timeout" or retries > 5 + try(dgram, datahost) + -- associate socket with data host/port + try(con:setpeername(datahost, dataport)) + -- default sink + local sink = gett.sink or ltn12.sink.null() + -- process all data packets + while 1 do + -- decode packet + code = get_OP(dgram) + try(code ~= OP_ERROR, get_ERROR(dgram)) + try(code == OP_DATA, "unhandled opcode " .. code) + -- get data packet parts + local block, data = split_DATA(dgram) + -- if not repeated, write + if block == last+1 then + try(sink(data)) + last = block + end + -- last packet brings less than 512 bytes of data + if string.len(data) < 512 then + try(con:send(ACK(block))) + try(con:close()) + try(sink(nil)) + return 1 + end + -- get the next packet + retries = 0 + repeat + sent = try(con:send(ACK(last))) + dgram, err = con:receive() + retries = retries + 1 + until dgram or err ~= "timeout" or retries > 5 + try(dgram, err) + end +end + +local default = { + port = PORT, + path ="/", + scheme = "tftp" +} + +local function parse(u) + local t = socket.try(url.parse(u, default)) + socket.try(t.scheme == "tftp", "invalid scheme '" .. t.scheme .. "'") + socket.try(t.host, "invalid host") + return t +end + +local function sget(u) + local gett = parse(u) + local t = {} + gett.sink = ltn12.sink.table(t) + tget(gett) + return table.concat(t) +end + +get = socket.protect(function(gett) + if base.type(gett) == "string" then return sget(gett) + else return tget(gett) end +end) + -- cgit v1.2.3-55-g6feb