aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authormassifrg <[email protected]>2025-06-16 01:14:36 +0200
committerJohn MacFarlane <[email protected]>2025-07-26 22:45:11 -0700
commitfe3684632b543b3d8a6b23de9da42dd87daedde7 (patch)
tree279ea56f1c2d06c8e9db2e1b144013ac0baa8ec4 /test
parentcf11339c1d3add1c4d758d0107d714b5954584fe (diff)
New `xml` format exactly representing a Pandoc AST.
This adds a reader and writer for an XML format equivalent to `native` and `json`. XML schemas for validation can be found in `tools/pandoc-xml.*`. The format is documented in `doc/xml.md`. API changes: - Add module Text.Pandoc.Readers.XML, exporting `readXML`. - Add module Text.Pandoc.Writers.XML, exporting `writeXML`. A new unexported module Text.Pandoc.XMLFormat is also added.
Diffstat (limited to 'test')
-rw-r--r--test/Tests/XML.hs28
-rw-r--r--test/test-pandoc.hs2
2 files changed, 30 insertions, 0 deletions
diff --git a/test/Tests/XML.hs b/test/Tests/XML.hs
new file mode 100644
index 000000000..71175917c
--- /dev/null
+++ b/test/Tests/XML.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+-- Module : Tests.XML
+-- Copyright : Copyright (C) 2025- Massimiliano Farinella and John MacFarlane
+-- License : GNU GPL, version 2 or above
+--
+-- Maintainer : Massimiliano Farinella <[email protected]>
+-- Stability : WIP
+-- Portability : portable
+Runs a roundtrip conversion of an AST trough the XML format:
+- first from AST to XML (XML Writer),
+- then back to AST (XML Reader),
+- and checks that the two ASTs are the same
+-}
+module Tests.XML (tests) where
+
+import Control.Monad ((>=>))
+import Test.Tasty (TestTree)
+import Test.Tasty.QuickCheck
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+
+p_xml_roundtrip :: Pandoc -> Bool
+p_xml_roundtrip d = d == purely (writeXML def {writerTemplate = Just mempty} >=> readXML def) d
+
+tests :: [TestTree]
+tests = [testProperty "p_xml_roundtrip" p_xml_roundtrip] \ No newline at end of file
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index 2f53c16be..6c6c2d1d4 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -50,6 +50,7 @@ import qualified Tests.Writers.RST
import qualified Tests.Writers.AnnotatedTable
import qualified Tests.Writers.TEI
import qualified Tests.Writers.Markua
+import qualified Tests.XML
import qualified Tests.MediaBag
import Text.Pandoc.Shared (inDirectory)
@@ -59,6 +60,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "Old" (Tests.Old.tests pandocPath)
, testGroup "Shared" Tests.Shared.tests
, testGroup "MediaBag" Tests.MediaBag.tests
+ , testGroup "XML" Tests.XML.tests
, testGroup "Writers"
[ testGroup "Native" Tests.Writers.Native.tests
, testGroup "ConTeXt" Tests.Writers.ConTeXt.tests