Lua filters: add SimpleTable for backwards compatibility (#6575)
A new type `SimpleTable` is made available to Lua filters. It is similar to the `Table` type in pandoc versions before 2.10; conversion functions from and to the new Table type are provided. Old filters using tables now require minimal changes and can use, e.g., if PANDOC_VERSION > {2,10,1} then pandoc.Table = pandoc.SimpleTable end and function Table (tbl) tbl = pandoc.utils.to_simple_table(tbl) … return pandoc.utils.from_simple_table(tbl) end to work with the current pandoc version.
This commit is contained in:
parent
b2decdfd13
commit
acbea6b8c6
10 changed files with 313 additions and 7 deletions
|
@ -78,6 +78,7 @@
|
|||
- Tests.Writers.Native
|
||||
- Text.Pandoc.Extensions
|
||||
- Text.Pandoc.Lua.Marshaling.Version
|
||||
- Text.Pandoc.Lua.Module.Utils
|
||||
- Text.Pandoc.Readers.Odt.ContentReader
|
||||
- Text.Pandoc.Readers.Odt.Namespaces
|
||||
|
||||
|
|
|
@ -1058,6 +1058,30 @@ M.ListAttributes.behavior.__pairs = function(t)
|
|||
return make_next_function(fields), t, nil
|
||||
end
|
||||
|
||||
--
|
||||
-- Legacy and compatibility types
|
||||
--
|
||||
|
||||
--- Creates a simple (old style) table element.
|
||||
-- @function SimpleTable
|
||||
-- @tparam {Inline,...} caption table caption
|
||||
-- @tparam {AlignDefault|AlignLeft|AlignRight|AlignCenter,...} aligns alignments
|
||||
-- @tparam {int,...} widths column widths
|
||||
-- @tparam {Block,...} headers header row
|
||||
-- @tparam {{Block,...}} rows table rows
|
||||
-- @treturn Block table element
|
||||
M.SimpleTable = function(caption, aligns, widths, headers, rows)
|
||||
return {
|
||||
caption = ensureInlineList(caption),
|
||||
aligns = List:new(aligns),
|
||||
widths = List:new(widths),
|
||||
headers = List:new(headers),
|
||||
rows = List:new(rows),
|
||||
tag = "SimpleTable",
|
||||
t = "SimpleTable",
|
||||
}
|
||||
end
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Constants
|
||||
|
|
|
@ -1744,6 +1744,36 @@ table into a List.
|
|||
A pandoc log message. Objects have no fields, but can be
|
||||
converted to a string via `tostring`.
|
||||
|
||||
## SimpleTable {#type-simpletable}
|
||||
|
||||
A simple table is a table structure which resembles the old (pre
|
||||
pandoc 2.10) Table type. Bi-directional conversion from and to
|
||||
[Tables](#type-table) is possible with the
|
||||
[`pandoc.utils.to_simple_table`](#pandoc.utils.to_simple_table)
|
||||
and
|
||||
[`pandoc.utils.from_simple_table`](#pandoc.utils.from_simple_table)
|
||||
function, respectively. Instances of this type can also be created
|
||||
directly with the [`pandoc.SimpleTable`](#pandoc.simpletable)
|
||||
constructor.
|
||||
|
||||
Fields:
|
||||
|
||||
`caption`:
|
||||
: [List] of [Inlines]
|
||||
|
||||
`aligns`:
|
||||
: column alignments ([List] of [Alignments](#type-alignment))
|
||||
|
||||
`widths`:
|
||||
: column widths; a ([List] of numbers)
|
||||
|
||||
`headers`:
|
||||
: table header row ([List] of lists of [Blocks])
|
||||
|
||||
`rows`:
|
||||
: table rows ([List] of rows, where a row is a list of lists of
|
||||
[Blocks])
|
||||
|
||||
## Version {#type-version}
|
||||
|
||||
A version object. This represents a software version like
|
||||
|
@ -1816,6 +1846,8 @@ Usage:
|
|||
[Pandoc]: #type-pandoc
|
||||
[Para]: #type-para
|
||||
[Rows]: #type-row
|
||||
[SimpleTable]: #type-simpletable
|
||||
[Table]: #type-table
|
||||
[TableBody]: #type-tablebody
|
||||
[TableFoot]: #type-tablefoot
|
||||
[TableHead]: #type-tablehead
|
||||
|
@ -2491,6 +2523,51 @@ format, and functions to filter and modify a subtree.
|
|||
|
||||
Returns: [ListAttributes](#type-listattributes) object
|
||||
|
||||
## Legacy types
|
||||
|
||||
[`SimpleTable (caption, aligns, widths, headers, rows)`]{#pandoc.simpletable}
|
||||
|
||||
: Creates a simple table resembling the old (pre pandoc 2.10)
|
||||
table type.
|
||||
|
||||
Parameters:
|
||||
|
||||
`caption`:
|
||||
: [List] of [Inlines]
|
||||
|
||||
`aligns`:
|
||||
: column alignments ([List] of [Alignments](#type-alignment))
|
||||
|
||||
`widths`:
|
||||
: column widths; a ([List] of numbers)
|
||||
|
||||
`headers`:
|
||||
: table header row ([List] of lists of [Blocks])
|
||||
|
||||
`rows`:
|
||||
: table rows ([List] of rows, where a row is a list of lists
|
||||
of [Blocks])
|
||||
|
||||
Returns: [SimpleTable] object
|
||||
|
||||
Usage:
|
||||
|
||||
local caption = "Overview"
|
||||
local aligns = {pandoc.AlignDefault, pandoc.AlignDefault}
|
||||
local widths = {0, 0} -- let pandoc determine col widths
|
||||
local headers = {"Language", "Typing"}
|
||||
local rows = {
|
||||
{{pandoc.Plain "Haskell"}, {pandoc.Plain "static"}},
|
||||
{{pandoc.Plain "Lua"}, {pandoc.Plain "Dynamic"}},
|
||||
}
|
||||
simple_table = pandoc.SimpleTable(
|
||||
caption,
|
||||
aligns,
|
||||
widths,
|
||||
headers,
|
||||
rows
|
||||
)
|
||||
|
||||
## Constants
|
||||
|
||||
[`AuthorInText`]{#pandoc.authorintext}
|
||||
|
@ -2753,6 +2830,26 @@ Returns:
|
|||
|
||||
- Whether the two objects represent the same element (boolean)
|
||||
|
||||
### from\_simple\_table {#pandoc.utils.from_simple_table}
|
||||
|
||||
`from_simple_table (table)`
|
||||
|
||||
Creates a [Table] block element from a [SimpleTable]. This is
|
||||
useful for dealing with legacy code which was written for pandoc
|
||||
versions older than 2.10.
|
||||
|
||||
Returns:
|
||||
|
||||
- table block element ([Table])
|
||||
|
||||
Usage:
|
||||
|
||||
local simple = pandoc.SimpleTable(table)
|
||||
-- modify, using pre pandoc 2.10 methods
|
||||
simple.caption = pandoc.SmallCaps(simple.caption)
|
||||
-- create normal table block again
|
||||
table = pandoc.utils.from_simple_table(simple)
|
||||
|
||||
### make\_sections {#pandoc.utils.make_sections}
|
||||
|
||||
`make_sections (number_sections, base_level, blocks)`
|
||||
|
@ -2872,6 +2969,24 @@ Usage:
|
|||
local pandoc_birth_year = to_roman_numeral(2006)
|
||||
-- pandoc_birth_year == 'MMVI'
|
||||
|
||||
### to\_simple\_table {#pandoc.utils.to_simple_table}
|
||||
|
||||
`to_simple_table (table)`
|
||||
|
||||
Creates a [SimpleTable] out of a [Table] block.
|
||||
|
||||
Returns:
|
||||
|
||||
- a simple table object ([SimpleTable])
|
||||
|
||||
Usage:
|
||||
|
||||
local simple = pandoc.utils.to_simple_table(table)
|
||||
-- modify, using pre pandoc 2.10 methods
|
||||
simple.caption = pandoc.SmallCaps(simple.caption)
|
||||
-- create normal table block again
|
||||
table = pandoc.utils.from_simple_table(simple)
|
||||
|
||||
# Module pandoc.mediabag
|
||||
|
||||
The `pandoc.mediabag` module allows accessing pandoc's media
|
||||
|
|
|
@ -633,6 +633,7 @@ library
|
|||
Text.Pandoc.Lua.Marshaling.MediaBag,
|
||||
Text.Pandoc.Lua.Marshaling.PandocError,
|
||||
Text.Pandoc.Lua.Marshaling.ReaderOptions,
|
||||
Text.Pandoc.Lua.Marshaling.SimpleTable,
|
||||
Text.Pandoc.Lua.Marshaling.Version,
|
||||
Text.Pandoc.Lua.Module.MediaBag,
|
||||
Text.Pandoc.Lua.Module.Pandoc,
|
||||
|
|
|
@ -80,6 +80,7 @@ putConstructorsInRegistry = liftPandocLua $ do
|
|||
putInReg "Attr" -- used for Attr type alias
|
||||
putInReg "ListAttributes" -- used for ListAttributes type alias
|
||||
putInReg "List" -- pandoc.List
|
||||
putInReg "SimpleTable" -- helper for backward-compatible table handling
|
||||
where
|
||||
constrsToReg :: Data a => a -> Lua ()
|
||||
constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
|
||||
|
|
|
@ -260,7 +260,7 @@ instance Peekable TableBody where
|
|||
return $ TableBody attr (RowHeadColumns rowHeadColumns) head' body
|
||||
|
||||
instance Pushable TableHead where
|
||||
push (TableHead attr cells) = Lua.push (attr, cells)
|
||||
push (TableHead attr rows) = Lua.push (attr, rows)
|
||||
|
||||
instance Peekable TableHead where
|
||||
peek = fmap (uncurry TableHead) . Lua.peek
|
||||
|
|
59
src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
Normal file
59
src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
Normal file
|
@ -0,0 +1,59 @@
|
|||
{- |
|
||||
Module : Text.Pandoc.Lua.Marshaling.SimpleTable
|
||||
Copyright : © 2020 Albert Krewinkel
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Stability : alpha
|
||||
|
||||
Definition and marshaling of the 'SimpleTable' data type used as a
|
||||
convenience type when dealing with tables.
|
||||
-}
|
||||
module Text.Pandoc.Lua.Marshaling.SimpleTable
|
||||
( SimpleTable (..)
|
||||
, peekSimpleTable
|
||||
, pushSimpleTable
|
||||
)
|
||||
where
|
||||
|
||||
import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor, rawField)
|
||||
import Text.Pandoc.Lua.Marshaling.AST ()
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
|
||||
-- | A simple (legacy-style) table.
|
||||
data SimpleTable = SimpleTable
|
||||
{ simpleTableCaption :: [Inline]
|
||||
, simpleTableAlignments :: [Alignment]
|
||||
, simpleTableColumnWidths :: [Double]
|
||||
, simpleTableHeader :: [[Block]]
|
||||
, simpleTableBody :: [[[Block]]]
|
||||
}
|
||||
|
||||
instance Pushable SimpleTable where
|
||||
push = pushSimpleTable
|
||||
|
||||
instance Peekable SimpleTable where
|
||||
peek = peekSimpleTable
|
||||
|
||||
-- | Push a simple table to the stack by calling the
|
||||
-- @pandoc.SimpleTable@ constructor.
|
||||
pushSimpleTable :: SimpleTable -> Lua ()
|
||||
pushSimpleTable tbl = pushViaConstructor "SimpleTable"
|
||||
(simpleTableCaption tbl)
|
||||
(simpleTableAlignments tbl)
|
||||
(simpleTableColumnWidths tbl)
|
||||
(simpleTableHeader tbl)
|
||||
(simpleTableBody tbl)
|
||||
|
||||
-- | Retrieve a simple table from the stack.
|
||||
peekSimpleTable :: StackIndex -> Lua SimpleTable
|
||||
peekSimpleTable idx = defineHowTo "get SimpleTable" $
|
||||
SimpleTable
|
||||
<$> rawField idx "caption"
|
||||
<*> rawField idx "aligns"
|
||||
<*> rawField idx "widths"
|
||||
<*> rawField idx "headers"
|
||||
<*> rawField idx "rows"
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua.Module.Utils
|
||||
|
@ -7,7 +8,7 @@
|
|||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Stability : alpha
|
||||
|
||||
Utility module for lua, exposing internal helper functions.
|
||||
Utility module for Lua, exposing internal helper functions.
|
||||
-}
|
||||
module Text.Pandoc.Lua.Module.Utils
|
||||
( pushModule
|
||||
|
@ -15,13 +16,17 @@ module Text.Pandoc.Lua.Module.Utils
|
|||
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Monad.Catch (try)
|
||||
import Data.Data (showConstr, toConstr)
|
||||
import Data.Default (def)
|
||||
import Data.Version (Version)
|
||||
import Foreign.Lua (Peekable, Lua, NumResults)
|
||||
import Text.Pandoc.Definition ( Pandoc, Meta, MetaValue (..), Block, Inline
|
||||
, Citation, Attr, ListAttributes)
|
||||
import Foreign.Lua (Peekable, Lua, NumResults (..))
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Error (PandocError)
|
||||
import Text.Pandoc.Lua.Marshaling ()
|
||||
import Text.Pandoc.Lua.Marshaling.SimpleTable
|
||||
( SimpleTable (..)
|
||||
, pushSimpleTable
|
||||
)
|
||||
import Text.Pandoc.Lua.PandocLua (PandocLua, addFunction, liftPandocLua)
|
||||
|
||||
import qualified Data.Digest.Pure.SHA as SHA
|
||||
|
@ -31,19 +36,22 @@ import qualified Foreign.Lua as Lua
|
|||
import qualified Text.Pandoc.Builder as B
|
||||
import qualified Text.Pandoc.Filter.JSON as JSONFilter
|
||||
import qualified Text.Pandoc.Shared as Shared
|
||||
import qualified Text.Pandoc.Writers.Shared as Shared
|
||||
|
||||
-- | Push the "pandoc.utils" module to the lua stack.
|
||||
-- | Push the "pandoc.utils" module to the Lua stack.
|
||||
pushModule :: PandocLua NumResults
|
||||
pushModule = do
|
||||
liftPandocLua Lua.newtable
|
||||
addFunction "blocks_to_inlines" blocksToInlines
|
||||
addFunction "equals" equals
|
||||
addFunction "from_simple_table" from_simple_table
|
||||
addFunction "make_sections" makeSections
|
||||
addFunction "normalize_date" normalizeDate
|
||||
addFunction "run_json_filter" runJSONFilter
|
||||
addFunction "sha1" sha1
|
||||
addFunction "stringify" stringify
|
||||
addFunction "to_roman_numeral" toRomanNumeral
|
||||
addFunction "to_simple_table" to_simple_table
|
||||
addFunction "Version" (return :: Version -> Lua Version)
|
||||
return 1
|
||||
|
||||
|
@ -131,6 +139,37 @@ instance Peekable AstElement where
|
|||
Left (_ :: PandocError) -> Lua.throwMessage
|
||||
"Expected an AST element, but could not parse value as such."
|
||||
|
||||
-- | Converts an old/simple table into a normal table block element.
|
||||
from_simple_table :: SimpleTable -> Lua NumResults
|
||||
from_simple_table (SimpleTable capt aligns widths head' body) = do
|
||||
Lua.push $ Table
|
||||
nullAttr
|
||||
(Caption Nothing [Plain capt])
|
||||
(zipWith (\a w -> (a, toColWidth w)) aligns widths)
|
||||
(TableHead nullAttr [blockListToRow head'])
|
||||
[TableBody nullAttr 0 [] $ map blockListToRow body]
|
||||
(TableFoot nullAttr [])
|
||||
return (NumResults 1)
|
||||
where
|
||||
blockListToRow :: [[Block]] -> Row
|
||||
blockListToRow = Row nullAttr . map (B.simpleCell . B.fromList)
|
||||
|
||||
toColWidth :: Double -> ColWidth
|
||||
toColWidth 0 = ColWidthDefault
|
||||
toColWidth w = ColWidth w
|
||||
|
||||
-- | Converts a table into an old/simple table.
|
||||
to_simple_table :: Block -> Lua NumResults
|
||||
to_simple_table = \case
|
||||
Table _attr caption specs thead tbodies tfoot -> do
|
||||
let (capt, aligns, widths, headers, rows) =
|
||||
Shared.toLegacyTable caption specs thead tbodies tfoot
|
||||
pushSimpleTable $ SimpleTable capt aligns widths headers rows
|
||||
return (NumResults 1)
|
||||
blk ->
|
||||
Lua.throwMessage $
|
||||
"Expected Table, got " <> showConstr (toConstr blk) <> "."
|
||||
|
||||
-- | Convert a number < 4000 to uppercase roman numeral.
|
||||
toRomanNumeral :: Lua.Integer -> PandocLua T.Text
|
||||
toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral
|
||||
|
|
|
@ -80,7 +80,7 @@ instance (Pushable a, PushViaCall b) => PushViaCall (a -> b) where
|
|||
pushViaCall :: PushViaCall a => String -> a
|
||||
pushViaCall fn = pushViaCall' fn (return ()) 0
|
||||
|
||||
-- | Call a pandoc element constructor within lua, passing all given arguments.
|
||||
-- | Call a pandoc element constructor within Lua, passing all given arguments.
|
||||
pushViaConstructor :: PushViaCall a => String -> a
|
||||
pushViaConstructor pandocFn = pushViaCall ("pandoc." ++ pandocFn)
|
||||
|
||||
|
|
|
@ -90,4 +90,70 @@ return {
|
|||
assert.is_falsy(pcall(utils.to_roman_numeral, 'not a number'))
|
||||
end)
|
||||
},
|
||||
|
||||
group 'to_simple_table' {
|
||||
test('convertes Table', function ()
|
||||
function simple_cell (blocks)
|
||||
return {
|
||||
attr = pandoc.Attr(),
|
||||
alignment = "AlignDefault",
|
||||
contents = blocks,
|
||||
col_span = 1,
|
||||
row_span = 1,
|
||||
}
|
||||
end
|
||||
local tbl = pandoc.Table(
|
||||
{long = {pandoc.Plain {
|
||||
pandoc.Str "the", pandoc.Space(), pandoc.Str "caption"}}},
|
||||
{{pandoc.AlignDefault, nil}},
|
||||
{pandoc.Attr(), {{pandoc.Attr(), {simple_cell{pandoc.Plain "head1"}}}}},
|
||||
{{
|
||||
attr = pandoc.Attr(),
|
||||
body = {{pandoc.Attr(), {simple_cell{pandoc.Plain "cell1"}}}},
|
||||
head = {},
|
||||
row_head_columns = 0
|
||||
}},
|
||||
{pandoc.Attr(), {}},
|
||||
pandoc.Attr()
|
||||
)
|
||||
local stbl = utils.to_simple_table(tbl)
|
||||
assert.are_equal('SimpleTable', stbl.t)
|
||||
assert.are_equal('head1', utils.stringify(stbl.headers[1]))
|
||||
assert.are_equal('cell1', utils.stringify(stbl.rows[1][1]))
|
||||
assert.are_equal('the caption', utils.stringify(pandoc.Span(stbl.caption)))
|
||||
end),
|
||||
test('fails on para', function ()
|
||||
assert.is_falsy(pcall(utils.to_simple_table, pandoc.Para "nope"))
|
||||
end),
|
||||
},
|
||||
group 'from_simple_table' {
|
||||
test('converts SimpleTable to Table', function ()
|
||||
local caption = {pandoc.Str "Overview"}
|
||||
local aligns = {pandoc.AlignDefault, pandoc.AlignDefault}
|
||||
local widths = {0, 0} -- let pandoc determine col widths
|
||||
local headers = {
|
||||
{pandoc.Plain "Language"},
|
||||
{pandoc.Plain "Typing"}
|
||||
}
|
||||
local rows = {
|
||||
{{pandoc.Plain "Haskell"}, {pandoc.Plain "static"}},
|
||||
{{pandoc.Plain "Lua"}, {pandoc.Plain "Dynamic"}},
|
||||
}
|
||||
local simple_table = pandoc.SimpleTable(
|
||||
caption,
|
||||
aligns,
|
||||
widths,
|
||||
headers,
|
||||
rows
|
||||
)
|
||||
local tbl = utils.from_simple_table(simple_table)
|
||||
assert.are_equal("Table", tbl.t)
|
||||
assert.are_same(
|
||||
{pandoc.Plain(caption)},
|
||||
tbl.caption.long
|
||||
)
|
||||
-- reversible
|
||||
assert.are_same(simple_table, utils.to_simple_table(tbl))
|
||||
end),
|
||||
}
|
||||
}
|
||||
|
|
Loading…
Add table
Reference in a new issue