aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
authorAnton Antich <[email protected]>2025-11-09 14:07:38 +0100
committerJohn MacFarlane <[email protected]>2025-11-24 23:10:33 +0100
commit59b8b3ed4b6998fad87b3a29ce59ba7a5cf40c46 (patch)
tree1ddde4712ae7f8a879bd1299ae408cc596b02a89 /test
parentec75b693e5618c12ddac872d48e084436f1e1b48 (diff)
Add `xlsx` (Microsoft Excel) as an input format.
Each worksheet turns into a section containing a table. The common file `nativeDiff` has been extract from the Docx and Pptx text files and put in Tests.Helpers.
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Helpers.hs14
-rw-r--r--test/Tests/Readers/Docx.hs14
-rw-r--r--test/Tests/Readers/Pptx.hs15
-rw-r--r--test/Tests/Readers/Xlsx.hs48
-rw-r--r--test/test-pandoc.hs4
-rw-r--r--test/xlsx-reader/basic.native381
-rw-r--r--test/xlsx-reader/basic.xlsxbin0 -> 13604 bytes
7 files changed, 446 insertions, 30 deletions
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
index 3e930b14a..081611ed9 100644
--- a/test/Tests/Helpers.hs
+++ b/test/Tests/Helpers.hs
@@ -16,6 +16,7 @@ module Tests.Helpers ( test
, TestResult(..)
, setupEnvironment
, showDiff
+ , nativeDiff
, testGolden
, (=?>)
, purely
@@ -132,6 +133,19 @@ vividize (Both s _) = " " ++ s
vividize (First s) = "- " ++ s
vividize (Second s) = "+ " ++ s
+nativeDiff :: FilePath -> Pandoc -> Pandoc -> IO (Maybe String)
+nativeDiff normPath expectedNative actualNative
+ | expectedNative == actualNative = return Nothing
+ | otherwise = Just <$> do
+ expected <- T.unpack <$> runIOorExplode (writeNative def expectedNative)
+ actual <- T.unpack <$> runIOorExplode (writeNative def actualNative)
+ let dash = replicate 72 '-'
+ let diff = getDiff (lines actual) (lines expected)
+ return $ '\n' : dash ++
+ "\n--- " ++ normPath ++
+ "\n+++ " ++ "test" ++ "\n" ++
+ showDiff (1,1) diff ++ dash
+
purely :: (b -> PandocPure a) -> b -> a
purely f = either (error . show) id . runPure . f
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 0bd70d0e2..76af649b4 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -34,20 +34,6 @@ defopts = def{ readerExtensions = getDefaultExtensions "docx" }
testCompare :: String -> FilePath -> FilePath -> TestTree
testCompare = testCompareWithOpts defopts
-
-nativeDiff :: FilePath -> Pandoc -> Pandoc -> IO (Maybe String)
-nativeDiff normPath expectedNative actualNative
- | expectedNative == actualNative = return Nothing
- | otherwise = Just <$> do
- expected <- T.unpack <$> runIOorExplode (writeNative def expectedNative)
- actual <- T.unpack <$> runIOorExplode (writeNative def actualNative)
- let dash = replicate 72 '-'
- let diff = getDiff (lines actual) (lines expected)
- return $ '\n' : dash ++
- "\n--- " ++ normPath ++
- "\n+++ " ++ "test" ++ "\n" ++
- showDiff (1,1) diff ++ dash
-
testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> TestTree
testCompareWithOpts opts testName docxFP nativeFP =
goldenTest
diff --git a/test/Tests/Readers/Pptx.hs b/test/Tests/Readers/Pptx.hs
index 613d5b50f..3358e4111 100644
--- a/test/Tests/Readers/Pptx.hs
+++ b/test/Tests/Readers/Pptx.hs
@@ -12,10 +12,8 @@ Tests for the PPTX reader.
-}
module Tests.Readers.Pptx (tests) where
-import Data.Algorithm.Diff (getDiff)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
-import qualified Data.Text as T
import Test.Tasty
import Test.Tasty.Golden.Advanced
import Tests.Helpers
@@ -28,19 +26,6 @@ defopts = def{ readerExtensions = getDefaultExtensions "pptx" }
testCompare :: String -> FilePath -> FilePath -> TestTree
testCompare = testCompareWithOpts defopts
-nativeDiff :: FilePath -> Pandoc -> Pandoc -> IO (Maybe String)
-nativeDiff normPath expectedNative actualNative
- | expectedNative == actualNative = return Nothing
- | otherwise = Just <$> do
- expected <- T.unpack <$> runIOorExplode (writeNative def expectedNative)
- actual <- T.unpack <$> runIOorExplode (writeNative def actualNative)
- let dash = replicate 72 '-'
- let diff = getDiff (lines actual) (lines expected)
- return $ '\n' : dash ++
- "\n--- " ++ normPath ++
- "\n+++ " ++ "test" ++ "\n" ++
- showDiff (1,1) diff ++ dash
-
testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> TestTree
testCompareWithOpts opts testName pptxFP nativeFP =
goldenTest
diff --git a/test/Tests/Readers/Xlsx.hs b/test/Tests/Readers/Xlsx.hs
new file mode 100644
index 000000000..189cd0c16
--- /dev/null
+++ b/test/Tests/Readers/Xlsx.hs
@@ -0,0 +1,48 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Tests.Readers.Xlsx
+ Copyright : © 2025 Anton Antic
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Anton Antic <[email protected]>
+ Stability : alpha
+ Portability : portable
+
+Tests for the XLSX reader.
+-}
+module Tests.Readers.Xlsx (tests) where
+
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as B
+import Test.Tasty
+import Test.Tasty.Golden.Advanced
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.UTF8 as UTF8
+
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "xlsx" }
+
+testCompare :: String -> FilePath -> FilePath -> TestTree
+testCompare = testCompareWithOpts defopts
+
+testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> TestTree
+testCompareWithOpts opts testName xlsxFP nativeFP =
+ goldenTest
+ testName
+ (do nf <- UTF8.toText <$> BS.readFile nativeFP
+ runIOorExplode (readNative def nf))
+ (do df <- B.readFile xlsxFP
+ runIOorExplode (readXlsx opts df))
+ (nativeDiff nativeFP)
+ (\a -> runIOorExplode (writeNative def{ writerTemplate = Just mempty} a)
+ >>= BS.writeFile nativeFP . UTF8.fromText)
+
+tests :: [TestTree]
+tests = [ testGroup "basic"
+ [ testCompare
+ "sheet extraction"
+ "xlsx-reader/basic.xlsx"
+ "xlsx-reader/basic.native"
+ ]
+ ]
diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs
index 0d04b361f..9ae97d9c0 100644
--- a/test/test-pandoc.hs
+++ b/test/test-pandoc.hs
@@ -13,6 +13,7 @@ import qualified Tests.Old
import qualified Tests.Readers.Creole
import qualified Tests.Readers.Docx
import qualified Tests.Readers.Pptx
+import qualified Tests.Readers.Xlsx
import qualified Tests.Readers.DokuWiki
import qualified Tests.Readers.EPUB
import qualified Tests.Readers.FB2
@@ -97,6 +98,7 @@ tests pandocPath = testGroup "pandoc tests"
, testGroup "RTF" Tests.Readers.RTF.tests
, testGroup "Docx" Tests.Readers.Docx.tests
, testGroup "Pptx" Tests.Readers.Pptx.tests
+ , testGroup "Xlsx" Tests.Readers.Xlsx.tests
, testGroup "ODT" Tests.Readers.ODT.tests
, testGroup "Txt2Tags" Tests.Readers.Txt2Tags.tests
, testGroup "EPUB" Tests.Readers.EPUB.tests
@@ -126,4 +128,4 @@ main = do
_ -> inDirectory "test" $ do
fp <- getExecutablePath
-- putStrLn $ "Using pandoc executable at " ++ fp
- defaultMain $ tests fp \ No newline at end of file
+ defaultMain $ tests fp
diff --git a/test/xlsx-reader/basic.native b/test/xlsx-reader/basic.native
new file mode 100644
index 000000000..f69f78a41
--- /dev/null
+++ b/test/xlsx-reader/basic.native
@@ -0,0 +1,381 @@
+Pandoc
+ Meta { unMeta = fromList [] }
+ [ Header 2 ( "sheet-1" , [] , [] ) [ Str "Main" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Strong [ Str "Person" ] ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Strong [ Str "Age" ] ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Strong [ Str "Location" ] ] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Anton" , Space , Str "Antich" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "23.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Switzerland" ] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "James" , Space , Str "Bond" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "35.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Moscow" ] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain
+ [ Str "Just"
+ , Space
+ , Str "a"
+ , Space
+ , Str "random"
+ , Space
+ , Str "cell"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ ]
+ ]
+ ]
+ (TableFoot ( "" , [] , [] ) [])
+ , Header 2 ( "sheet-2" , [] , [] ) [ Str "Secondary" ]
+ , Table
+ ( "" , [] , [] )
+ (Caption Nothing [])
+ [ ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ , ( AlignDefault , ColWidthDefault )
+ ]
+ (TableHead
+ ( "" , [] , [] )
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain
+ [ Str "Sum"
+ , Space
+ , Str "of"
+ , Space
+ , Str "Age"
+ ]
+ ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Column" , Space , Str "Labels" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ ]
+ ])
+ [ TableBody
+ ( "" , [] , [] )
+ (RowHeadColumns 0)
+ []
+ [ Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Row" , Space , Str "Labels" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Moscow" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Switzerland" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "(blank)" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Grand" , Space , Str "Total" ] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Anton" , Space , Str "Antich" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "23.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "23.0" ] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "James" , Space , Str "Bond" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "35.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "35.0" ] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "(blank)" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ ]
+ , Row
+ ( "" , [] , [] )
+ [ Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "Grand" , Space , Str "Total" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "35.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "23.0" ] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [] ]
+ , Cell
+ ( "" , [] , [] )
+ AlignDefault
+ (RowSpan 1)
+ (ColSpan 1)
+ [ Plain [ Str "58.0" ] ]
+ ]
+ ]
+ ]
+ (TableFoot ( "" , [] , [] ) [])
+ ]
diff --git a/test/xlsx-reader/basic.xlsx b/test/xlsx-reader/basic.xlsx
new file mode 100644
index 000000000..55d62d56e
--- /dev/null
+++ b/test/xlsx-reader/basic.xlsx
Binary files differ