aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2018-11-19 21:36:02 +0100
committerAlbert Krewinkel <albert@zeitkraut.de>2018-11-19 21:46:20 +0100
commitc0d8b0abcb99adf5f7d2ddac3ad343d48da94910 (patch)
treea417b0f20fd0f297c41e686b1d2120698e27424c /src/Text/Pandoc/Lua/Module
parente80bcb9bea4e39dd62a984695f2c72d1a9a83ee2 (diff)
downloadpandoc-c0d8b0abcb99adf5f7d2ddac3ad343d48da94910.tar.gz
Lua filters: test AST object equality via Haskell
Equality of Lua objects representing pandoc AST elements is tested by unmarshalling the objects and comparing the result in Haskell. A new function `equals` which performs this test has been added to the `pandoc.utils` module. Closes: #5092
Diffstat (limited to 'src/Text/Pandoc/Lua/Module')
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs18
1 files changed, 15 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 01762aebf..a75a2934b 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE NoImplicitPrelude #-}
{-
Copyright © 2017-2018 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -15,7 +16,6 @@ You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
-{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Text.Pandoc.Lua.Module.Utils
Copyright : Copyright © 2017-2018 Albert Krewinkel
@@ -36,7 +36,8 @@ import Data.Char (toLower)
import Data.Default (def)
import Foreign.Lua (Peekable, Lua, NumResults)
import Text.Pandoc.Class (runIO, setUserDataDir)
-import Text.Pandoc.Definition (Pandoc, Meta, MetaValue (..), Block, Inline)
+import Text.Pandoc.Definition ( Pandoc, Meta, MetaValue (..), Block, Inline
+ , Citation, Attr, ListAttributes)
import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Lua.Util (addFunction)
@@ -52,6 +53,7 @@ pushModule :: Maybe FilePath -> Lua NumResults
pushModule mbDatadir = do
Lua.newtable
addFunction "blocks_to_inlines" blocksToInlines
+ addFunction "equals" equals
addFunction "hierarchicalize" hierarchicalize
addFunction "normalize_date" normalizeDate
addFunction "run_json_filter" (runJSONFilter mbDatadir)
@@ -112,7 +114,9 @@ stringify el = return $ case el of
InlineElement i -> Shared.stringify i
BlockElement b -> Shared.stringify b
MetaElement m -> Shared.stringify m
+ CitationElement c -> Shared.stringify c
MetaValueElement m -> stringifyMetaValue m
+ _ -> ""
stringifyMetaValue :: MetaValue -> String
stringifyMetaValue mv = case mv of
@@ -120,19 +124,27 @@ stringifyMetaValue mv = case mv of
MetaString s -> s
_ -> Shared.stringify mv
+equals :: AstElement -> AstElement -> Lua Bool
+equals e1 e2 = return (e1 == e2)
+
data AstElement
= PandocElement Pandoc
| MetaElement Meta
| BlockElement Block
| InlineElement Inline
| MetaValueElement MetaValue
- deriving (Show)
+ | AttrElement Attr
+ | ListAttributesElement ListAttributes
+ | CitationElement Citation
+ deriving (Eq, Show)
instance Peekable AstElement where
peek idx = do
res <- Lua.try $ (PandocElement <$> Lua.peek idx)
<|> (InlineElement <$> Lua.peek idx)
<|> (BlockElement <$> Lua.peek idx)
+ <|> (AttrElement <$> Lua.peek idx)
+ <|> (ListAttributesElement <$> Lua.peek idx)
<|> (MetaElement <$> Lua.peek idx)
<|> (MetaValueElement <$> Lua.peek idx)
case res of