aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2020-09-21 00:48:31 +0200
committerGitHub <noreply@github.com>2020-09-20 15:48:31 -0700
commitacbea6b8c610dba4b63c0f6063c51b26ab9d2b76 (patch)
tree2140ee75afafc3d87ca3d50c4cd989efec221a51 /src/Text/Pandoc/Lua/Marshaling
parentb2decdfd1370b5291a6c1be758d4e0bfeaf9fcc7 (diff)
downloadpandoc-acbea6b8c610dba4b63c0f6063c51b26ab9d2b76.tar.gz
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.
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling')
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/AST.hs2
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs59
2 files changed, 60 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs
index 679dd1f46..c889618c4 100644
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs
@@ -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
diff --git a/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs b/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
new file mode 100644
index 000000000..98fa1efa4
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
@@ -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"