diff options
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling/AST.hs')
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/AST.hs | 105 |
1 files changed, 100 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index a4087ad87..81b206f67 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -150,7 +150,7 @@ peekMetaValue idx = defineHowTo "get MetaValue" $ do <|> (MetaList <$> Lua.peek idx) _ -> Lua.throwException "could not get meta value" --- | Push an block element to the top of the lua stack. +-- | Push a block element to the top of the Lua stack. pushBlock :: Block -> Lua () pushBlock = \case BlockQuote blcks -> pushViaConstructor "BlockQuote" blcks @@ -167,8 +167,8 @@ pushBlock = \case Para blcks -> pushViaConstructor "Para" blcks Plain blcks -> pushViaConstructor "Plain" blcks RawBlock f cs -> pushViaConstructor "RawBlock" f cs - Table capt aligns widths headers rows -> - pushViaConstructor "Table" capt aligns widths headers rows + Table attr blkCapt specs thead tbody tfoot -> + pushViaConstructor "Table" attr blkCapt specs thead tbody tfoot -- | Return the value at the given index as block if possible. peekBlock :: StackIndex -> Lua Block @@ -191,8 +191,13 @@ peekBlock idx = defineHowTo "get Block value" $ do "Para" -> Para <$> elementContent "Plain" -> Plain <$> elementContent "RawBlock" -> uncurry RawBlock <$> elementContent - "Table" -> (\(capt, aligns, widths, headers, body) -> - Table capt aligns widths headers body) + "Table" -> (\(attr, capt, colSpecs, thead, tbodies, tfoot) -> + Table (fromLuaAttr attr) + capt + colSpecs + thead + tbodies + tfoot) <$> elementContent _ -> Lua.throwException ("Unknown block type: " <> tag) where @@ -200,6 +205,96 @@ peekBlock idx = defineHowTo "get Block value" $ do elementContent :: Peekable a => Lua a elementContent = LuaUtil.rawField idx "c" +instance Pushable Caption where + push = pushCaption + +instance Peekable Caption where + peek = peekCaption + +-- | Push Caption element +pushCaption :: Caption -> Lua () +pushCaption (Caption shortCaption longCaption) = do + Lua.newtable + LuaUtil.addField "short" (Lua.Optional shortCaption) + LuaUtil.addField "long" longCaption + +-- | Peek Caption element +peekCaption :: StackIndex -> Lua Caption +peekCaption idx = do + short <- Lua.fromOptional <$> LuaUtil.rawField idx "short" + long <- LuaUtil.rawField idx "long" + return $ Caption short long + +instance Peekable ColWidth where + peek idx = do + width <- Lua.fromOptional <$> Lua.peek idx + return $ case width of + Nothing -> ColWidthDefault + Just w -> ColWidth w + +instance Pushable ColWidth where + push = \case + (ColWidth w) -> Lua.push w + ColWidthDefault -> Lua.pushnil + +instance Pushable Row where + push (Row attr cells) = Lua.push (attr, cells) + +instance Peekable Row where + peek = fmap (uncurry Row) . Lua.peek + +instance Pushable TableBody where + push (TableBody attr (RowHeadColumns rowHeadColumns) head' body) = do + Lua.newtable + LuaUtil.addField "attr" attr + LuaUtil.addField "row_head_columns" rowHeadColumns + LuaUtil.addField "head" head' + LuaUtil.addField "body" body + +instance Peekable TableBody where + peek idx = do + attr <- LuaUtil.rawField idx "attr" + rowHeadColumns <- LuaUtil.rawField idx "row_head_columns" + head' <- LuaUtil.rawField idx "head" + body <- LuaUtil.rawField idx "body" + return $ TableBody attr (RowHeadColumns rowHeadColumns) head' body + +instance Pushable TableHead where + push (TableHead attr cells) = Lua.push (attr, cells) + +instance Peekable TableHead where + peek = fmap (uncurry TableHead) . Lua.peek + +instance Pushable TableFoot where + push (TableFoot attr cells) = Lua.push (attr, cells) + +instance Peekable TableFoot where + peek = fmap (uncurry TableFoot) . Lua.peek + +instance Pushable Cell where + push = pushCell + +instance Peekable Cell where + peek = peekCell + +pushCell :: Cell -> Lua () +pushCell (Cell attr align (RowSpan rowSpan) (ColSpan colSpan) contents) = do + Lua.newtable + LuaUtil.addField "attr" attr + LuaUtil.addField "alignment" align + LuaUtil.addField "row_span" rowSpan + LuaUtil.addField "col_span" colSpan + LuaUtil.addField "contents" contents + +peekCell :: StackIndex -> Lua Cell +peekCell idx = do + attr <- fromLuaAttr <$> LuaUtil.rawField idx "attr" + align <- LuaUtil.rawField idx "alignment" + rowSpan <- LuaUtil.rawField idx "row_span" + colSpan <- LuaUtil.rawField idx "col_span" + contents <- LuaUtil.rawField idx "contents" + return $ Cell attr align (RowSpan rowSpan) (ColSpan colSpan) contents + -- | Push an inline element to the top of the lua stack. pushInline :: Inline -> Lua () pushInline = \case |