Skip to content

Commit

Permalink
[WIP] Walk cells
Browse files Browse the repository at this point in the history
  • Loading branch information
tarleb committed Jul 2, 2024
1 parent ab4f4be commit c27c56e
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 0 deletions.
35 changes: 35 additions & 0 deletions src/Text/Pandoc/Lua/Marshal/Cell.hs-boot
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
{- |
Copyright : © 2021-2024 Albert Krewinkel
SPDX-License-Identifier : MIT
Maintainer : Albert Krewinkel <[email protected]>
Marshaling/unmarshaling functions of table 'Cell' values.
-}
module Text.Pandoc.Lua.Marshal.Cell
( peekCell
, peekCellFuzzy
, pushCell
, typeCell
, mkCell
) where

import HsLua
import Text.Pandoc.Definition

-- | Push a table cell as a table with fields @attr@, @alignment@,
-- @row_span@, @col_span@, and @contents@.
pushCell :: LuaError e => Cell -> LuaE e ()

-- | Retrieves a 'Cell' object from the stack.
peekCell :: LuaError e => Peeker e Cell

-- | Retrieves a 'Cell' from the stack, accepting either a 'pandoc Cell'
-- userdata object or a table with fields @attr@, @alignment@, @row_span@,
-- @col_span@, and @contents@.
peekCellFuzzy :: LuaError e => Peeker e Cell

-- | Cell object type.
typeCell :: LuaError e => DocumentedType e Cell

-- | Constructor function for 'Cell' values.
mkCell :: LuaError e => DocumentedFunction e
9 changes: 9 additions & 0 deletions src/Text/Pandoc/Lua/Marshal/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Prelude hiding (lookup)
import Control.Monad ((>=>))
import HsLua
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Block
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Cell
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Inline
import Text.Pandoc.Lua.Marshal.Filter
import Text.Pandoc.Definition
Expand Down Expand Up @@ -82,3 +83,11 @@ applyFilterTopdown filter' topdown@(Topdown _ node) =
(inlines, ctrl) <-
applyStraightFunction fn pushInlines peekInlinesFuzzy xs
pure $ Topdown ctrl $ TInlines inlines
TCell c ->
case "Cell" `lookup` filter' of
Nothing ->
pure topdown
Just fn -> do
(cell, ctrl) <-
applyStraightFunction fn pushCell peekCellFuzzy c
pure $ Topdown ctrl $ TCell cell
4 changes: 4 additions & 0 deletions src/Text/Pandoc/Lua/Topdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,8 @@ data TraversalNode
| TBlocks [Block]
| TInline Inline
| TInlines [Inline]
-- | TRow Row
| TCell Cell

-- | Type used to traverse a 'Pandoc' AST from top to bottom, i.e.,
-- processing the root element first and then continue towards the
Expand All @@ -56,6 +58,8 @@ nodeBlocks = \case
TBlock x -> [x]
TInlines xs -> [Plain xs]
TInline x -> [Plain [x]]
TCell c -> let Cell _attr _align _rowspan _colspan blks = c
in blks

-- | Creates a topdown-walking function for a list of elements.
walkTopdownM :: (Monad m, Walkable Topdown a)
Expand Down

0 comments on commit c27c56e

Please sign in to comment.