aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module
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/Module
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/Module')
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs49
1 files changed, 44 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 988489a2a..7595b9c0f 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -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