Skip to content

Commit

Permalink
Handle lints raised by Luacheck
Browse files Browse the repository at this point in the history
  • Loading branch information
alerque committed Aug 28, 2024
1 parent eb662fa commit 8f705c8
Show file tree
Hide file tree
Showing 21 changed files with 69 additions and 74 deletions.
4 changes: 1 addition & 3 deletions data/creole.lua
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,7 @@
-- http://www.wikicreole.org/wiki/CheatSheet

-- For better performance we put these functions in local variables:
local P, S, R, Cf, Cc, Ct, V, Cs, Cg, Cb, B, C, Cmt =
lpeg.P, lpeg.S, lpeg.R, lpeg.Cf, lpeg.Cc, lpeg.Ct, lpeg.V,
lpeg.Cs, lpeg.Cg, lpeg.Cb, lpeg.B, lpeg.C, lpeg.Cmt
local P, S, Cc, Ct, V, C = lpeg.P, lpeg.S, lpeg.Cc, lpeg.Ct, lpeg.V, lpeg.C

local whitespacechar = S(" \t\r\n")
local specialchar = S("/*~[]\\{}|")
Expand Down
8 changes: 4 additions & 4 deletions man/manfilter.lua
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ local text = require('text')
function Header(el)
if el.level == 1 then
return pandoc.walk_block(el, {
Str = function(el)
return pandoc.Str(text.upper(el.text))
Str = function(str_el)
return pandoc.Str(text.upper(str_el.text))
end })
end
end
Expand All @@ -21,7 +21,7 @@ function Table(el)
return " " .. string.rep("-", #s - 1)
end)
:gsub("(%+[-:][-:]+)",
function(s)
function(_)
return ""
end)
:gsub("%+\n","\n")
Expand All @@ -39,6 +39,6 @@ function Link(el)
end

-- remove notes
function Note(el)
function Note(_)
return {}
end
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/bytestring-reader.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
function ByteStringReader (input, opts)
function ByteStringReader (input, _)
local chars = pandoc.List{}
for i = 1, #input do
chars:insert(utf8.char(input:byte(i,i)))
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/bytestring.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
function ByteStringWriter (doc, opts)
function ByteStringWriter (_, _)
local buffer = {}
for i=0, 255 do
table.insert(buffer, string.char(i))
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/extensions.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
function Writer (doc, opts)
function Writer (_, opts)
local output = 'smart extension is %s;\ncitations extension is %s\n'
local status = function (ext)
return opts.extensions:includes(ext) and 'enabled' or 'disabled'
Expand Down
4 changes: 2 additions & 2 deletions pandoc-lua-engine/test/lua/block-count.lua
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
local num_blocks = 0

function Block(el)
function Block(_)
num_blocks = num_blocks + 1
end

function Pandoc(blocks, meta)
function Pandoc(_, _)
return pandoc.Pandoc {
pandoc.Para{pandoc.Str(num_blocks)}
}
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/hello-world-doc.lua
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
return {
{
Pandoc = function(doc)
Pandoc = function(_)
local meta = {}
local hello = { pandoc.Str "Hello,", pandoc.Space(), pandoc.Str "World!" }
local blocks = { pandoc.Para(hello) }
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/implicit-doc-filter.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
function Pandoc (doc)
function Pandoc (_)
local meta = {}
local hello = { pandoc.Str "Hello,", pandoc.Space(), pandoc.Str "World!" }
local blocks = { pandoc.Para(hello) }
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/inlines-filter.lua
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
function isWorldAfterSpace (fst, snd)
local function isWorldAfterSpace (fst, snd)
return fst and fst.t == 'LineBreak'
and snd and snd.t == 'Str' and snd.text == 'World!'
end
Expand Down
4 changes: 2 additions & 2 deletions pandoc-lua-engine/test/lua/metatable-catch-all.lua
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
local num_inlines = 0

function catch_all(el)
local function catch_all(el)
if el.tag and pandoc.Inline.constructor[el.tag] then
num_inlines = num_inlines + 1
end
end

function Pandoc(blocks, meta)
function Pandoc(_, _)
return pandoc.Pandoc {
pandoc.Para{pandoc.Str(num_inlines)}
}
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/module/pandoc-json.lua
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ return {
local obj = setmetatable(
{title = 23},
{
__tojson = function (obj)
__tojson = function (_)
return '"Nichts ist so wie es scheint"'
end
}
Expand Down
4 changes: 2 additions & 2 deletions pandoc-lua-engine/test/lua/module/pandoc-list.lua
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ local group = tasty.test_group

return {
group 'List as function' {
test('equivalent to List:new', function (x)
test('equivalent to List:new', function (_)
local new = List:new {'ramen'}
local list = List {'ramen'}
assert.are_same(new, list)
Expand Down Expand Up @@ -109,7 +109,7 @@ return {
end),
test('leaves original list unchanged', function ()
local primes = List:new {2, 3, 5, 7}
local squares = primes:map(function (x) return x^2 end)
local _ = primes:map(function (x) return x^2 end)
assert.are_same({2, 3, 5, 7}, primes)
end)
},
Expand Down
2 changes: 0 additions & 2 deletions pandoc-lua-engine/test/lua/module/pandoc-structure.lua
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
local tasty = require 'tasty'
local structure = require 'pandoc.structure'
local path = require 'pandoc.path'
local system = require 'pandoc.system'

local assert = tasty.assert
local test = tasty.test_case
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/module/pandoc-template.lua
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ return {
)
end),
test('fails on unknown format', function ()
local success, msg = pcall(function ()
local success, _ = pcall(function ()
return pandoc.utils.type(template.default 'nosuchformat')
end)
assert.is_falsy(success)
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/module/pandoc-utils.lua
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,7 @@ return {

group 'to_simple_table' {
test('convertes Table', function ()
function simple_cell (blocks)
local function simple_cell (blocks)
return {
attr = pandoc.Attr(),
alignment = "AlignDefault",
Expand Down
2 changes: 1 addition & 1 deletion pandoc-lua-engine/test/lua/module/pandoc.lua
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ local test = tasty.test_case
local group = tasty.test_group
local assert = tasty.assert

function os_is_windows ()
local function os_is_windows ()
return package.config:sub(1,1) == '\\'
end

Expand Down
7 changes: 3 additions & 4 deletions pandoc-lua-engine/test/sample.lua
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ function Writer (doc, opts)
end

local pipe = pandoc.pipe
local stringify = (require 'pandoc.utils').stringify

-- Choose the image format based on the value of the
-- `image_format` environment variable.
Expand Down Expand Up @@ -80,7 +79,7 @@ end
-- This gives you a fragment. You could use the metadata table to
-- fill variables in a custom lua template. Or, pass `--template=...`
-- to pandoc, and pandoc will do the template processing as usual.
function Doc(body, metadata, variables)
function Doc(body, _, _)
local buffer = {}
local function add(s)
table.insert(buffer, s)
Expand Down Expand Up @@ -146,7 +145,7 @@ function Link(s, tgt, tit, attr)
escape(tit,true) .. '"' .. attributes(attr) .. '>' .. s .. '</a>'
end

function Image(s, src, tit, attr)
function Image(_, src, tit, _ttr)
return '<img src="' .. escape(src,true) .. '" title="' ..
escape(tit,true) .. '"/>'
end
Expand Down Expand Up @@ -283,7 +282,7 @@ local function html_align(align)
end
end

function CaptionedImage(src, tit, caption, attr)
function CaptionedImage(src, _, caption, attr)
if #caption == 0 then
return '<p><img src="' .. escape(src,true) .. '" id="' .. attr.id ..
'"/></p>'
Expand Down
2 changes: 1 addition & 1 deletion tools/extract-changes.lua
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@

function Pandoc(el)
local newblocks = {}
i = 1
local i = 1
while i <= #el.blocks and
not (el.blocks[i].t == "Header" and el.blocks[i].level == 2) do
i = i+1
Expand Down
6 changes: 3 additions & 3 deletions tools/moduledeps.lua
Original file line number Diff line number Diff line change
Expand Up @@ -35,11 +35,11 @@ end

local transitive = {}

function prind(ind, s)
local function prind(ind, s)
io.write(string.rep(" ",ind) .. s .. "\n")
end

function add_transitive_deps(mod)
local function add_transitive_deps(mod)
if transitive[mod] then
return
end
Expand All @@ -53,7 +53,7 @@ function add_transitive_deps(mod)
end
end

function print_direct_deps(mod, ind)
local function print_direct_deps(mod, ind)
ind = ind or 0
prind(ind, mod)
for dep,_ in pairs(dependencies[mod]) do
Expand Down
78 changes: 39 additions & 39 deletions tools/update-lua-module-docs.lua
Original file line number Diff line number Diff line change
@@ -1,13 +1,12 @@
local ipairs, load, next, pairs, print, tostring, type, warn =
ipairs, load, next, pairs, print, tostring, type, warn
local ipairs, next, pairs, print, tostring, type, warn =
ipairs, next, pairs, print, tostring, type, warn
local string, table = string, table
local _G, arg = _G, arg

local registry = debug.getregistry()

_ENV = pandoc

local stringify = utils.stringify
local utils, read, write, List = pandoc.utils, pandoc.read, pandoc.write, pandoc.List
-- local stringify = pandoc.utils.stringify

--- Retrieves the documentation object for the given value.
local function documentation (value)
Expand All @@ -21,7 +20,7 @@ local function sorted (tbl)
end
table.sort(keys)
local i = 0
local iter = function (state, ctrl)
local iter = function (_, ctrl)
if i > 0 and ctrl == nil then
return nil
else
Expand All @@ -32,9 +31,9 @@ local function sorted (tbl)
return iter, nil, nil
end

local get = function (fieldname)
return function (obj) return obj[fieldname] end
end
-- local get = function (fieldname)
-- return function (obj) return obj[fieldname] end
-- end

local function read_blocks (txt)
return read(txt, 'commonmark+smart+wikilinks_title_before_pipe').blocks
Expand Down Expand Up @@ -101,7 +100,7 @@ end
local function argslist (parameters)
local required = List{}
local optional = List{}
for i, param in ipairs(parameters) do
for _, param in ipairs(parameters) do
if param.optional then
optional:insert(param.name)
else
Expand Down Expand Up @@ -186,7 +185,7 @@ local function render_type (name, level, modulename)
local propattr = {'type-' .. id .. '-properties'}
properties:insert(Header(level + 1, "Properties", propattr))
for propname, prop in sorted(metatable.docs.properties) do
attr = {'type-' .. nameprefix .. '.' .. name .. '.' .. propname}
local attr = {'type-' .. nameprefix .. '.' .. name .. '.' .. propname}
properties:insert(Header(level + 2, propname, attr))
properties:insert(
Plain(read_inlines(prop.description) ..
Expand All @@ -199,6 +198,7 @@ local function render_type (name, level, modulename)
if next(metatable.methods) then
local attr = {'type-' .. id .. '-methods'}
methods:insert(Header(level + 1, "Methods", attr))
-- luacheck: ignore propname
for propname, method in sorted(metatable.methods) do
-- attr = {'type-' .. modulename .. '.' .. name .. '.' .. propname}
-- methods:insert(Header(level + 2, propname, attr))
Expand All @@ -217,15 +217,15 @@ local function render_module (doc)
local fields = Blocks{}
if #doc.fields > 0 then
fields:insert(Header(2, 'Fields', {doc.name .. '-' .. 'fields'}))
for i, fld in ipairs(doc.fields) do
for _, fld in ipairs(doc.fields) do
fields:extend(render_field(fld, 3, doc.name))
end
end

local functions = Blocks{}
if #doc.functions > 0 then
functions:insert(Header(2, 'Functions', {doc.name .. '-' .. 'functions'}))
for i, fun in ipairs(doc.functions) do
for _, fun in ipairs(doc.functions) do
functions:extend(render_function(fun, 3, doc.name))
end
end
Expand All @@ -234,7 +234,7 @@ local function render_module (doc)
local types = type(doc.types) == 'function' and doc.types() or {}
if #types > 0 then
typedocs:insert(Header(2, 'Types', {doc.name .. '-' .. 'types'}))
for i, ty in ipairs(types) do
for _, ty in ipairs(types) do
typedocs:extend(render_type(ty, 3, doc.name))
end
end
Expand All @@ -247,29 +247,29 @@ local function render_module (doc)
typedocs
end

local function get_module_name(header)
return stringify(header):match 'Module pandoc%.([%w]*)'
end

--- Set of modules for which documentation should be generated.
local handled_modules = {
layout = true
}

local modules = {
-- 'cli',
-- 'utils',
-- 'mediabag',
-- 'format',
-- 'path',
-- 'structure',
-- 'system',
-- 'layout',
-- 'scaffolding',
-- 'template',
-- 'types',
'zip',
}
-- local function get_module_name(header)
-- return stringify(header):match 'Module pandoc%.([%w]*)'
-- end

-- --- Set of modules for which documentation should be generated.
-- local handled_modules = {
-- layout = true
-- }

-- local modules = {
-- -- 'cli',
-- -- 'utils',
-- -- 'mediabag',
-- -- 'format',
-- -- 'path',
-- -- 'structure',
-- -- 'system',
-- -- 'layout',
-- -- 'scaffolding',
-- -- 'template',
-- -- 'types',
-- 'zip',
-- }

-- Generate docs for the given module
if arg and arg[1] then
Expand Down Expand Up @@ -299,13 +299,13 @@ local function foo (input, blocks, start)
blocks:extend(render_module(documentation(object)))
return foo(input, blocks, input:find(autogen_end, mstop) or -1)
else
local reflinks_start, reflinks_stop = input:find(reflinks_marker, start)
local _, reflinks_stop = input:find(reflinks_marker, start)
blocks:insert(rawmd(input:sub(start, reflinks_stop)))
return blocks
end
end

function _G.Reader (inputs, opts)
function _G.Reader (inputs, _)
local blocks = foo(tostring(inputs), Blocks{}, 1)
blocks = blocks:walk {
Link = function (link)
Expand Down
Loading

0 comments on commit 8f705c8

Please sign in to comment.