aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 21:39:24 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 21:45:16 +0200
commitb95e864ecfc0a0ef96fa09d4118c8e6b4033784c (patch)
tree65b6cbf01483bbf7d932d82bb95c8549cc69799f /src/Text/Pandoc/Lua/Marshaling
parent80ed81822e27ac0d09e365ccc6f6508f3b1b4a9b (diff)
downloadpandoc-b95e864ecfc0a0ef96fa09d4118c8e6b4033784c.tar.gz
Lua: marshal SimpleTable values as userdata objects
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling')
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs74
1 files changed, 56 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs b/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
index e9c169dc0..65f5aec8b 100644
--- a/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/SimpleTable.hs
@@ -1,13 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Marshaling.SimpleTable
Copyright : © 2020-2021 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.
@@ -16,14 +13,14 @@ module Text.Pandoc.Lua.Marshaling.SimpleTable
( SimpleTable (..)
, peekSimpleTable
, pushSimpleTable
+ , mkSimpleTable
)
where
-import Control.Monad ((<$!>))
import HsLua as Lua
import Text.Pandoc.Definition
-import Text.Pandoc.Lua.Util (pushViaConstructor)
import Text.Pandoc.Lua.Marshaling.AST
+import Text.Pandoc.Lua.Marshaling.List
-- | A simple (legacy-style) table.
data SimpleTable = SimpleTable
@@ -32,23 +29,64 @@ data SimpleTable = SimpleTable
, simpleTableColumnWidths :: [Double]
, simpleTableHeader :: [[Block]]
, simpleTableBody :: [[[Block]]]
- }
+ } deriving (Eq, Show)
+
+typeSimpleTable :: LuaError e => DocumentedType e SimpleTable
+typeSimpleTable = deftype "SimpleTable"
+ [ operation Eq $ lambda
+ ### liftPure2 (==)
+ <#> udparam typeSimpleTable "a" ""
+ <#> udparam typeSimpleTable "b" ""
+ =#> functionResult pushBool "boolean" "whether the two objects are equal"
+ , operation Tostring $ lambda
+ ### liftPure show
+ <#> udparam typeSimpleTable "self" ""
+ =#> functionResult pushString "string" "Haskell string representation"
+ ]
+ [ property "caption" "table caption"
+ (pushPandocList pushInline, simpleTableCaption)
+ (peekInlinesFuzzy, \t capt -> t {simpleTableCaption = capt})
+ , property "aligns" "column alignments"
+ (pushPandocList (pushString . show), simpleTableAlignments)
+ (peekList peekRead, \t aligns -> t{simpleTableAlignments = aligns})
+ , property "widths" "relative column widths"
+ (pushPandocList pushRealFloat, simpleTableColumnWidths)
+ (peekList peekRealFloat, \t ws -> t{simpleTableColumnWidths = ws})
+ , property "headers" "table header"
+ (pushRow, simpleTableHeader)
+ (peekRow, \t h -> t{simpleTableHeader = h})
+ , property "rows" "table body rows"
+ (pushPandocList pushRow, simpleTableBody)
+ (peekList peekRow, \t bs -> t{simpleTableBody = bs})
+
+ , readonly "t" "type tag (always 'SimpleTable')"
+ (pushText, const "SimpleTable")
+
+ , alias "header" "alias for `headers`" ["headers"]
+ ]
+ where
+ pushRow = pushPandocList (pushPandocList pushBlock)
+
+peekRow :: LuaError e => Peeker e [[Block]]
+peekRow = peekList peekBlocksFuzzy
-- | Push a simple table to the stack by calling the
-- @pandoc.SimpleTable@ constructor.
pushSimpleTable :: forall e. LuaError e => SimpleTable -> LuaE e ()
-pushSimpleTable tbl = pushViaConstructor @e "SimpleTable"
- (simpleTableCaption tbl)
- (simpleTableAlignments tbl)
- (simpleTableColumnWidths tbl)
- (simpleTableHeader tbl)
- (simpleTableBody tbl)
+pushSimpleTable = pushUD typeSimpleTable
-- | Retrieve a simple table from the stack.
peekSimpleTable :: forall e. LuaError e => Peeker e SimpleTable
-peekSimpleTable idx = retrieving "SimpleTable" $ SimpleTable
- <$!> peekFieldRaw peekInlines "caption" idx
- <*> peekFieldRaw (peekList peekRead) "aligns" idx
- <*> peekFieldRaw (peekList peekRealFloat) "widths" idx
- <*> peekFieldRaw (peekList peekBlocks) "headers" idx
- <*> peekFieldRaw (peekList (peekList peekBlocks)) "rows" idx
+peekSimpleTable = retrieving "SimpleTable" . peekUD typeSimpleTable
+
+-- | Constructor for the 'SimpleTable' type.
+mkSimpleTable :: LuaError e => DocumentedFunction e
+mkSimpleTable = defun "SimpleTable"
+ ### liftPure5 SimpleTable
+ <#> parameter peekInlinesFuzzy "Inlines" "caption" "table caption"
+ <#> parameter (peekList peekRead) "{Alignment,...}" "align" "column alignments"
+ <#> parameter (peekList peekRealFloat) "{number,...}" "widths"
+ "relative column widths"
+ <#> parameter peekRow "{Blocks,...}" "header" "table header row"
+ <#> parameter (peekList peekRow) "{{Blocks,...},...}" "body" "table body rows"
+ =#> functionResult pushSimpleTable "SimpleTable" "new SimpleTable object"