summaryrefslogtreecommitdiff
path: root/test/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests')
-rw-r--r--test/Tests/Command.hs95
-rw-r--r--test/Tests/Helpers.hs138
-rw-r--r--test/Tests/Lua.hs196
-rw-r--r--test/Tests/Old.hs289
-rw-r--r--test/Tests/Readers/Creole.hs286
-rw-r--r--test/Tests/Readers/Docx.hs401
-rw-r--r--test/Tests/Readers/EPUB.hs40
-rw-r--r--test/Tests/Readers/HTML.hs54
-rw-r--r--test/Tests/Readers/JATS.hs116
-rw-r--r--test/Tests/Readers/LaTeX.hs341
-rw-r--r--test/Tests/Readers/Markdown.hs462
-rw-r--r--test/Tests/Readers/Muse.hs1224
-rw-r--r--test/Tests/Readers/Odt.hs170
-rw-r--r--test/Tests/Readers/Org.hs16
-rw-r--r--test/Tests/Readers/Org/Block.hs192
-rw-r--r--test/Tests/Readers/Org/Block/CodeBlock.hs194
-rw-r--r--test/Tests/Readers/Org/Block/Figure.hs57
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs182
-rw-r--r--test/Tests/Readers/Org/Block/List.hs244
-rw-r--r--test/Tests/Readers/Org/Block/Table.hs150
-rw-r--r--test/Tests/Readers/Org/Directive.hs199
-rw-r--r--test/Tests/Readers/Org/Inline.hs352
-rw-r--r--test/Tests/Readers/Org/Inline/Citation.hs179
-rw-r--r--test/Tests/Readers/Org/Inline/Note.hs86
-rw-r--r--test/Tests/Readers/Org/Inline/Smart.hs46
-rw-r--r--test/Tests/Readers/Org/Meta.hs191
-rw-r--r--test/Tests/Readers/Org/Shared.hs29
-rw-r--r--test/Tests/Readers/RST.hs189
-rw-r--r--test/Tests/Readers/Txt2Tags.hs437
-rw-r--r--test/Tests/Shared.hs39
-rw-r--r--test/Tests/Writers/AsciiDoc.hs56
-rw-r--r--test/Tests/Writers/ConTeXt.hs149
-rw-r--r--test/Tests/Writers/Docbook.hs303
-rw-r--r--test/Tests/Writers/Docx.hs157
-rw-r--r--test/Tests/Writers/FB2.hs34
-rw-r--r--test/Tests/Writers/HTML.hs44
-rw-r--r--test/Tests/Writers/JATS.hs122
-rw-r--r--test/Tests/Writers/LaTeX.hs176
-rw-r--r--test/Tests/Writers/Markdown.hs267
-rw-r--r--test/Tests/Writers/Muse.hs385
-rw-r--r--test/Tests/Writers/Native.hs22
-rw-r--r--test/Tests/Writers/OOXML.hs184
-rw-r--r--test/Tests/Writers/Org.hs25
-rw-r--r--test/Tests/Writers/Plain.hs21
-rw-r--r--test/Tests/Writers/Powerpoint.hs93
-rw-r--r--test/Tests/Writers/RST.hs117
-rw-r--r--test/Tests/Writers/TEI.hs43
47 files changed, 8792 insertions, 0 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
new file mode 100644
index 000000000..de83d0639
--- /dev/null
+++ b/test/Tests/Command.hs
@@ -0,0 +1,95 @@
+module Tests.Command (findPandoc, runTest, tests)
+where
+
+import Data.Algorithm.Diff
+import qualified Data.ByteString as BS
+import Data.List (isSuffixOf)
+import Prelude hiding (readFile)
+import System.Directory
+import System.Exit
+import System.FilePath (joinPath, splitDirectories, takeDirectory, (</>))
+import System.IO (hPutStr, stderr)
+import System.IO.Unsafe (unsafePerformIO)
+import System.Process
+import Test.Tasty
+import Test.Tasty.HUnit
+import Tests.Helpers
+import Text.Pandoc
+import qualified Text.Pandoc.UTF8 as UTF8
+
+-- | Run a test with normalize function, return True if test passed.
+runTest :: String -- ^ Title of test
+ -> FilePath -- ^ Path to pandoc
+ -> String -- ^ Shell command
+ -> String -- ^ Input text
+ -> String -- ^ Expected output
+ -> TestTree
+runTest testname pandocpath cmd inp norm = testCase testname $ do
+ let findDynlibDir [] = Nothing
+ findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
+ findDynlibDir (_:xs) = findDynlibDir xs
+ let mbDynlibDir = findDynlibDir (reverse $ splitDirectories $
+ takeDirectory $ takeWhile (/=' ') cmd)
+ let dynlibEnv = case mbDynlibDir of
+ Nothing -> []
+ Just d -> [("DYLD_LIBRARY_PATH", d),
+ ("LD_LIBRARY_PATH", d)]
+ let env' = dynlibEnv ++ [("PATH",takeDirectory pandocpath),("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./"),("pandoc_datadir", "..")]
+ let pr = (shell cmd){ env = Just env' }
+ (ec, out', err') <- readCreateProcessWithExitCode pr inp
+ -- filter \r so the tests will work on Windows machines
+ let out = filter (/= '\r') $ err' ++ out'
+ result <- if ec == ExitSuccess
+ then
+ if out == norm
+ then return TestPassed
+ else return
+ $ TestFailed cmd "expected"
+ $ getDiff (lines out) (lines norm)
+ else do
+ hPutStr stderr err'
+ return $ TestError ec
+ assertBool (show result) (result == TestPassed)
+
+tests :: TestTree
+{-# NOINLINE tests #-}
+tests = unsafePerformIO $ do
+ pandocpath <- findPandoc
+ files <- filter (".md" `isSuffixOf`) <$>
+ getDirectoryContents "command"
+ let cmds = map (extractCommandTest pandocpath) files
+ return $ testGroup "Command:" cmds
+
+isCodeBlock :: Block -> Bool
+isCodeBlock (CodeBlock _ _) = True
+isCodeBlock _ = False
+
+extractCode :: Block -> String
+extractCode (CodeBlock _ code) = code
+extractCode _ = ""
+
+dropPercent :: String -> String
+dropPercent ('%':xs) = dropWhile (== ' ') xs
+dropPercent xs = xs
+
+runCommandTest :: FilePath -> (Int, String) -> TestTree
+runCommandTest pandocpath (num, code) =
+ let codelines = lines code
+ (continuations, r1) = span ("\\" `isSuffixOf`) codelines
+ (cmd, r2) = (dropPercent (unwords (map init continuations ++ take 1 r1)),
+ drop 1 r1)
+ (inplines, r3) = break (=="^D") r2
+ normlines = takeWhile (/=".") (drop 1 r3)
+ input = unlines inplines
+ norm = unlines normlines
+ shcmd = cmd -- trimr $ takeDirectory pandocpath </> cmd
+ in runTest ("#" ++ show num) pandocpath shcmd input norm
+
+extractCommandTest :: FilePath -> FilePath -> TestTree
+extractCommandTest pandocpath fp = unsafePerformIO $ do
+ contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
+ Pandoc _ blocks <- runIOorExplode (readMarkdown
+ def{ readerExtensions = pandocExtensions } contents)
+ let codeblocks = map extractCode $ filter isCodeBlock blocks
+ let cases = map (runCommandTest pandocpath) $ zip [1..] codeblocks
+ return $ testGroup fp cases
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
new file mode 100644
index 000000000..2a6543ea0
--- /dev/null
+++ b/test/Tests/Helpers.hs
@@ -0,0 +1,138 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE TypeSynonymInstances #-}
+-- Utility functions for the test suite.
+
+module Tests.Helpers ( test
+ , TestResult(..)
+ , showDiff
+ , findPandoc
+ , (=?>)
+ , purely
+ , ToString(..)
+ , ToPandoc(..)
+ )
+ where
+
+import Data.Algorithm.Diff
+import qualified Data.Map as M
+import Data.Text (Text, unpack)
+import System.Directory
+import System.Environment.Executable (getExecutablePath)
+import System.Exit
+import System.FilePath
+import Test.Tasty
+import Test.Tasty.HUnit
+import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
+import Text.Pandoc.Class
+import Text.Pandoc.Definition
+import Text.Pandoc.Options
+import Text.Pandoc.Shared (trimr)
+import Text.Pandoc.Writers.Native (writeNative)
+import Text.Printf
+
+test :: (ToString a, ToString b, ToString c)
+ => (a -> b) -- ^ function to test
+ -> String -- ^ name of test case
+ -> (a, c) -- ^ (input, expected value)
+ -> TestTree
+test fn name (input, expected) =
+ testCase name' $ assertBool msg (actual' == expected')
+ where msg = nl ++ dashes "input" ++ nl ++ input' ++ nl ++
+ dashes "result" ++ nl ++
+ unlines (map vividize diff) ++
+ dashes ""
+ nl = "\n"
+ name' = if length name > 54
+ then take 52 name ++ "..." -- avoid wide output
+ else name
+ input' = toString input
+ actual' = lines $ toString $ fn input
+ expected' = lines $ toString expected
+ diff = getDiff expected' actual'
+ dashes "" = replicate 72 '-'
+ dashes x = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
+
+data TestResult = TestPassed
+ | TestError ExitCode
+ | TestFailed String FilePath [Diff String]
+ deriving (Eq)
+
+instance Show TestResult where
+ show TestPassed = "PASSED"
+ show (TestError ec) = "ERROR " ++ show ec
+ show (TestFailed cmd file d) = '\n' : dash ++
+ "\n--- " ++ file ++
+ "\n+++ " ++ cmd ++ "\n" ++ showDiff (1,1) d ++
+ dash
+ where dash = replicate 72 '-'
+
+showDiff :: (Int,Int) -> [Diff String] -> String
+showDiff _ [] = ""
+showDiff (l,r) (First ln : ds) =
+ printf "+%4d " l ++ ln ++ "\n" ++ showDiff (l+1,r) ds
+showDiff (l,r) (Second ln : ds) =
+ printf "-%4d " r ++ ln ++ "\n" ++ showDiff (l,r+1) ds
+showDiff (l,r) (Both _ _ : ds) =
+ showDiff (l+1,r+1) ds
+
+-- | Find pandoc executable relative to test-pandoc
+-- First, try in same directory (e.g. if both in ~/.cabal/bin)
+-- Second, try ../pandoc (e.g. if in dist/XXX/build/test-pandoc)
+findPandoc :: IO FilePath
+findPandoc = do
+ testExePath <- getExecutablePath
+ let testExeDir = takeDirectory testExePath
+ found <- doesFileExist (testExeDir </> "pandoc")
+ return $ if found
+ then testExeDir </> "pandoc"
+ else case splitDirectories testExeDir of
+ [] -> error "test-pandoc: empty testExeDir"
+ xs -> joinPath (init xs) </> "pandoc" </> "pandoc"
+
+
+vividize :: Diff String -> String
+vividize (Both s _) = " " ++ s
+vividize (First s) = "- " ++ s
+vividize (Second s) = "+ " ++ s
+
+purely :: (b -> PandocPure a) -> b -> a
+purely f = either (error . show) id . runPure . f
+
+infix 5 =?>
+(=?>) :: a -> b -> (a,b)
+x =?> y = (x, y)
+
+class ToString a where
+ toString :: a -> String
+
+instance ToString Pandoc where
+ toString d = unpack $
+ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ where s = case d of
+ (Pandoc (Meta m) _)
+ | M.null m -> Nothing
+ | otherwise -> Just "" -- need this to get meta output
+
+instance ToString Blocks where
+ toString = unpack . purely (writeNative def) . toPandoc
+
+instance ToString Inlines where
+ toString = trimr . unpack . purely (writeNative def) . toPandoc
+
+instance ToString String where
+ toString = id
+
+instance ToString Text where
+ toString = unpack
+
+class ToPandoc a where
+ toPandoc :: a -> Pandoc
+
+instance ToPandoc Pandoc where
+ toPandoc = id
+
+instance ToPandoc Blocks where
+ toPandoc = doc
+
+instance ToPandoc Inlines where
+ toPandoc = doc . plain
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
new file mode 100644
index 000000000..4599e544d
--- /dev/null
+++ b/test/Tests/Lua.hs
@@ -0,0 +1,196 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Lua ( tests ) where
+
+import Control.Monad (when)
+import Data.Version (Version (versionBranch))
+import System.FilePath ((</>))
+import Test.Tasty (TestTree, localOption)
+import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
+import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
+ header, linebreak, para, plain, rawBlock,
+ singleQuoted, space, str, strong, (<>))
+import Text.Pandoc.Class (runIOorExplode, setUserDataDir)
+import Text.Pandoc.Definition (Block (BlockQuote, Div, Para), Inline (Emph, Str),
+ Attr, Meta, Pandoc, pandocTypesVersion)
+import Text.Pandoc.Lua (runLuaFilter, runPandocLua)
+import Text.Pandoc.Options (def)
+import Text.Pandoc.Shared (pandocVersion)
+
+import qualified Foreign.Lua as Lua
+
+tests :: [TestTree]
+tests = map (localOption (QuickCheckTests 20))
+ [ testProperty "inline elements can be round-tripped through the lua stack" $
+ \x -> ioProperty (roundtripEqual (x::Inline))
+
+ , testProperty "block elements can be round-tripped through the lua stack" $
+ \x -> ioProperty (roundtripEqual (x::Block))
+
+ , testProperty "meta blocks can be round-tripped through the lua stack" $
+ \x -> ioProperty (roundtripEqual (x::Meta))
+
+ , testProperty "documents can be round-tripped through the lua stack" $
+ \x -> ioProperty (roundtripEqual (x::Pandoc))
+
+ , testCase "macro expansion via filter" $
+ assertFilterConversion "a '{{helloworld}}' string is expanded"
+ "strmacro.lua"
+ (doc . para $ str "{{helloworld}}")
+ (doc . para . emph $ str "Hello, World")
+
+ , testCase "convert all plains to paras" $
+ assertFilterConversion "plains become para"
+ "plain-to-para.lua"
+ (doc $ bulletList [plain (str "alfa"), plain (str "bravo")])
+ (doc $ bulletList [para (str "alfa"), para (str "bravo")])
+
+ , testCase "make hello world document" $
+ assertFilterConversion "Document contains 'Hello, World!'"
+ "hello-world-doc.lua"
+ (doc . para $ str "Hey!" <> linebreak <> str "What's up?")
+ (doc . para $ str "Hello," <> space <> str "World!")
+
+ , testCase "implicit doc filter" $
+ assertFilterConversion "Document contains 'Hello, World!'"
+ "implicit-doc-filter.lua"
+ (doc . plain $ linebreak)
+ (doc . para $ str "Hello," <> space <> str "World!")
+
+ , testCase "parse raw markdown blocks" $
+ assertFilterConversion "raw markdown block is converted"
+ "markdown-reader.lua"
+ (doc $ rawBlock "markdown" "*charly* **delta**")
+ (doc . para $ emph "charly" <> space <> strong "delta")
+
+ , testCase "allow shorthand functions for quote types" $
+ assertFilterConversion "single quoted becomes double quoted string"
+ "single-to-double-quoted.lua"
+ (doc . para . singleQuoted $ str "simple")
+ (doc . para . doubleQuoted $ str "simple")
+
+ , testCase "Count inlines via metatable catch-all" $
+ assertFilterConversion "filtering with metatable catch-all failed"
+ "metatable-catch-all.lua"
+ (doc . para $ "four words, three spaces")
+ (doc . para $ str "7")
+
+ , testCase "Count blocks via Block-specific catch-all" $
+ assertFilterConversion "filtering with Block catch-all failed"
+ "block-count.lua"
+ (doc $ para "one" <> para "two")
+ (doc $ para "2")
+
+ , testCase "Convert header upper case" $
+ assertFilterConversion "converting header to upper case failed"
+ "uppercase-header.lua"
+ (doc $ header 1 "les états-unis" <> para "text")
+ (doc $ header 1 "LES ÉTATS-UNIS" <> para "text")
+
+ , testCase "Attribute lists are convenient to use" $
+ let kv_before = [("one", "1"), ("two", "2"), ("three", "3")]
+ kv_after = [("one", "eins"), ("three", "3"), ("five", "5")]
+ in assertFilterConversion "Attr doesn't behave as expected"
+ "attr-test.lua"
+ (doc $ divWith ("", [], kv_before) (para "nil"))
+ (doc $ divWith ("", [], kv_after) (para "nil"))
+
+ , testCase "Test module pandoc.utils" $
+ assertFilterConversion "pandoc.utils doesn't work as expected."
+ "test-pandoc-utils.lua"
+ (doc $ para "doesn't matter")
+ (doc $ mconcat [ plain (str "hierarchicalize: OK")
+ , plain (str "normalize_date: OK")
+ , plain (str "pipe: OK")
+ , plain (str "failing pipe: OK")
+ , plain (str "read: OK")
+ , plain (str "failing read: OK")
+ , plain (str "sha1: OK")
+ , plain (str "stringify: OK")
+ , plain (str "to_roman_numeral: OK")
+ ])
+
+ , testCase "Script filename is set" $
+ assertFilterConversion "unexpected script name"
+ "script-name.lua"
+ (doc $ para "ignored")
+ (doc $ para (str $ "lua" </> "script-name.lua"))
+
+ , testCase "Pandoc version is set" . runPandocLua' $ do
+ Lua.getglobal' "table.concat"
+ Lua.getglobal "PANDOC_VERSION"
+ Lua.push ("." :: String) -- seperator
+ Lua.call 2 1
+ Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion
+ =<< Lua.peek Lua.stackTop
+
+ , testCase "Pandoc types version is set" . runPandocLua' $ do
+ let versionNums = versionBranch pandocTypesVersion
+ Lua.getglobal "PANDOC_API_VERSION"
+ Lua.liftIO . assertEqual "pandoc-types version is wrong" versionNums
+ =<< Lua.peek Lua.stackTop
+
+ , testCase "Allow singleton inline in constructors" . runPandocLua' $ do
+ Lua.liftIO . assertEqual "Not the exptected Emph" (Emph [Str "test"])
+ =<< Lua.callFunc "pandoc.Emph" (Str "test")
+ Lua.liftIO . assertEqual "Unexpected element" (Para [Str "test"])
+ =<< Lua.callFunc "pandoc.Para" ("test" :: String)
+ Lua.liftIO . assertEqual "Unexptected element"
+ (BlockQuote [Para [Str "foo"]]) =<< (
+ do
+ Lua.getglobal' "pandoc.BlockQuote"
+ Lua.push (Para [Str "foo"])
+ _ <- Lua.call 1 1
+ Lua.peek Lua.stackTop
+ )
+
+ , testCase "Elements with Attr have `attr` accessor" . runPandocLua' $ do
+ Lua.push (Div ("hi", ["moin"], [])
+ [Para [Str "ignored"]])
+ Lua.getfield Lua.stackTop "attr"
+ Lua.liftIO . assertEqual "no accessor" (("hi", ["moin"], []) :: Attr)
+ =<< Lua.peek Lua.stackTop
+
+ , testCase "informative error messages" . runPandocLua' $ do
+ Lua.pushboolean True
+ err <- Lua.peekEither Lua.stackTop :: Lua.Lua (Either String Pandoc)
+ case err of
+ Left msg -> do
+ let expectedMsg = "Could not get Pandoc value: "
+ ++ "expected table but got boolean."
+ Lua.liftIO $ assertEqual "unexpected error message" expectedMsg msg
+ Right _ -> error "Getting a Pandoc element from a bool should fail."
+ ]
+
+assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
+assertFilterConversion msg filterPath docIn docExpected = do
+ docEither <- runIOorExplode $ do
+ setUserDataDir (Just "../data")
+ runLuaFilter def ("lua" </> filterPath) [] docIn
+ case docEither of
+ Left _ -> fail "lua filter failed"
+ Right docRes -> assertEqual msg docExpected docRes
+
+roundtripEqual :: (Eq a, Lua.FromLuaStack a, Lua.ToLuaStack a) => a -> IO Bool
+roundtripEqual x = (x ==) <$> roundtripped
+ where
+ roundtripped :: (Lua.FromLuaStack a, Lua.ToLuaStack a) => IO a
+ roundtripped = runPandocLua' $ do
+ oldSize <- Lua.gettop
+ Lua.push x
+ size <- Lua.gettop
+ when (size - oldSize /= 1) $
+ error ("not exactly one additional element on the stack: " ++ show size)
+ res <- Lua.peekEither (-1)
+ case res of
+ Left e -> error (show e)
+ Right y -> return y
+
+runPandocLua' :: Lua.Lua a -> IO a
+runPandocLua' op = runIOorExplode $ do
+ setUserDataDir (Just "../data")
+ res <- runPandocLua op
+ case res of
+ Left e -> error (show e)
+ Right x -> return x
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
new file mode 100644
index 000000000..b82251a56
--- /dev/null
+++ b/test/Tests/Old.hs
@@ -0,0 +1,289 @@
+module Tests.Old (tests) where
+
+import Data.Algorithm.Diff
+import Prelude hiding (readFile)
+import System.Exit
+import System.FilePath (joinPath, splitDirectories, (<.>), (</>))
+import System.IO.Temp (withTempFile)
+import System.Process (runProcess, waitForProcess)
+import Test.Tasty (TestTree, testGroup)
+import Test.Tasty.Golden.Advanced (goldenTest)
+import Tests.Helpers hiding (test)
+import qualified Text.Pandoc.UTF8 as UTF8
+
+tests :: [TestTree]
+tests = [ testGroup "markdown"
+ [ testGroup "writer"
+ $ writerTests "markdown" ++ lhsWriterTests "markdown"
+ , testGroup "reader"
+ [ test "basic" ["-r", "markdown", "-w", "native", "-s"]
+ "testsuite.txt" "testsuite.native"
+ , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"]
+ "tables.txt" "tables.native"
+ , test "pipe tables" ["-r", "markdown", "-w", "native", "--columns=80"]
+ "pipe-tables.txt" "pipe-tables.native"
+ , test "more" ["-r", "markdown", "-w", "native", "-s"]
+ "markdown-reader-more.txt" "markdown-reader-more.native"
+ , lhsReaderTest "markdown+lhs"
+ ]
+ , testGroup "citations"
+ [ test "citations" ["-r", "markdown", "-w", "native"]
+ "markdown-citations.txt" "markdown-citations.native"
+ ]
+ ]
+ , testGroup "rst"
+ [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst")
+ , testGroup "reader"
+ [ test "basic" ["-r", "rst+smart", "-w", "native",
+ "-s", "--columns=80"] "rst-reader.rst" "rst-reader.native"
+ , test "tables" ["-r", "rst", "-w", "native", "--columns=80"]
+ "tables.rst" "tables-rstsubset.native"
+ , lhsReaderTest "rst+lhs"
+ ]
+ ]
+ , testGroup "latex"
+ [ testGroup "writer" (writerTests "latex" ++ lhsWriterTests "latex")
+ , testGroup "reader"
+ [ test "basic" ["-r", "latex+raw_tex", "-w", "native", "-s"]
+ "latex-reader.latex" "latex-reader.native"
+ , lhsReaderTest "latex+lhs"
+ ]
+ ]
+ , testGroup "html"
+ [ testGroup "writer" (writerTests "html4" ++ writerTests "html5" ++
+ lhsWriterTests "html")
+ , test "reader" ["-r", "html", "-w", "native", "-s"]
+ "html-reader.html" "html-reader.native"
+ ]
+ , testGroup "s5"
+ [ s5WriterTest "basic" ["-s"] "s5"
+ , s5WriterTest "fancy" ["-s","-m","-i"] "s5"
+ , s5WriterTest "fragment" [] "html4"
+ , s5WriterTest "inserts" ["-s", "-H", "insert",
+ "-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
+ ]
+ , testGroup "textile"
+ [ testGroup "writer" $ writerTests "textile"
+ , test "reader" ["-r", "textile", "-w", "native", "-s"]
+ "textile-reader.textile" "textile-reader.native"
+ ]
+ , testGroup "docbook"
+ [ testGroup "writer" $ writerTests "docbook4"
+ , test "reader" ["-r", "docbook", "-w", "native", "-s"]
+ "docbook-reader.docbook" "docbook-reader.native"
+ , test "reader" ["-r", "docbook", "-w", "native", "-s"]
+ "docbook-xref.docbook" "docbook-xref.native"
+ ]
+ , testGroup "docbook5"
+ [ testGroup "writer" $ writerTests "docbook5"
+ ]
+ , testGroup "jats"
+ [ testGroup "writer" $ writerTests "jats"
+ , test "reader" ["-r", "jats", "-w", "native", "-s"]
+ "jats-reader.xml" "jats-reader.native"
+ ]
+ , testGroup "native"
+ [ testGroup "writer" $ writerTests "native"
+ , test "reader" ["-r", "native", "-w", "native", "-s"]
+ "testsuite.native" "testsuite.native"
+ ]
+ , testGroup "fb2"
+ [ fb2WriterTest "basic" [] "fb2/basic.markdown" "fb2/basic.fb2"
+ , fb2WriterTest "titles" [] "fb2/titles.markdown" "fb2/titles.fb2"
+ , fb2WriterTest "images" [] "fb2/images.markdown" "fb2/images.fb2"
+ , fb2WriterTest "images-embedded" [] "fb2/images-embedded.html" "fb2/images-embedded.fb2"
+ , fb2WriterTest "math" [] "fb2/math.markdown" "fb2/math.fb2"
+ , fb2WriterTest "tables" [] "tables.native" "tables.fb2"
+ , fb2WriterTest "testsuite" [] "testsuite.native" "writer.fb2"
+ ]
+ , testGroup "mediawiki"
+ [ testGroup "writer" $ writerTests "mediawiki"
+ , test "reader" ["-r", "mediawiki", "-w", "native", "-s"]
+ "mediawiki-reader.wiki" "mediawiki-reader.native"
+ ]
+ , testGroup "vimwiki"
+ [ test "reader" ["-r", "vimwiki", "-w", "native", "-s"]
+ "vimwiki-reader.wiki" "vimwiki-reader.native"
+ ]
+ , testGroup "dokuwiki"
+ [ testGroup "writer" $ writerTests "dokuwiki"
+ , test "inline_formatting" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki_inline_formatting.native" "dokuwiki_inline_formatting.dokuwiki"
+ , test "multiblock table" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki_multiblock_table.native" "dokuwiki_multiblock_table.dokuwiki"
+ , test "external images" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki_external_images.native" "dokuwiki_external_images.dokuwiki"
+ ]
+ , testGroup "opml"
+ [ test "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
+ "testsuite.native" "writer.opml"
+ , test "reader" ["-r", "opml", "-w", "native", "-s"]
+ "opml-reader.opml" "opml-reader.native"
+ ]
+ , testGroup "haddock"
+ [ testGroup "writer" $ writerTests "haddock"
+ , test "reader" ["-r", "haddock", "-w", "native", "-s"]
+ "haddock-reader.haddock" "haddock-reader.native"
+ ]
+ , testGroup "txt2tags"
+ [ test "reader" ["-r", "t2t", "-w", "native", "-s"]
+ "txt2tags.t2t" "txt2tags.native" ]
+ , testGroup "epub" [
+ test "features" ["-r", "epub", "-w", "native"]
+ "epub/features.epub" "epub/features.native"
+ , test "wasteland" ["-r", "epub", "-w", "native"]
+ "epub/wasteland.epub" "epub/wasteland.native"
+ , test "formatting" ["-r", "epub", "-w", "native"]
+ "epub/formatting.epub" "epub/formatting.native"
+ ]
+ , testGroup "twiki"
+ [ test "reader" ["-r", "twiki", "-w", "native", "-s"]
+ "twiki-reader.twiki" "twiki-reader.native" ]
+ , testGroup "tikiwiki"
+ [ test "reader" ["-r", "tikiwiki", "-w", "native", "-s"]
+ "tikiwiki-reader.tikiwiki" "tikiwiki-reader.native" ]
+ , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
+ [ "opendocument" , "context" , "texinfo", "icml", "tei"
+ , "man" , "plain" , "rtf", "org", "asciidoc", "zimwiki"
+ ]
+ , testGroup "writers-lang-and-dir"
+ [ test "latex" ["-f", "native", "-t", "latex", "-s"]
+ "writers-lang-and-dir.native" "writers-lang-and-dir.latex"
+ , test "context" ["-f", "native", "-t", "context", "-s"]
+ "writers-lang-and-dir.native" "writers-lang-and-dir.context"
+ ]
+ , testGroup "muse"
+ [ testGroup "writer" $ writerTests "muse"
+ ]
+ , testGroup "ms"
+ [ testGroup "writer" $ writerTests "ms"
+ ]
+ , testGroup "creole"
+ [ test "reader" ["-r", "creole", "-w", "native", "-s"]
+ "creole-reader.txt" "creole-reader.native"
+ ]
+ , testGroup "custom writer"
+ [ test "basic" ["-f", "native", "-t", "../data/sample.lua"]
+ "testsuite.native" "writer.custom"
+ , test "tables" ["-f", "native", "-t", "../data/sample.lua"]
+ "tables.native" "tables.custom"
+ ]
+ ]
+
+-- makes sure file is fully closed after reading
+readFile' :: FilePath -> IO String
+readFile' f = do s <- UTF8.readFile f
+ return $! (length s `seq` s)
+
+lhsWriterTests :: String -> [TestTree]
+lhsWriterTests format
+ = [ t "lhs to normal" format
+ , t "lhs to lhs" (format ++ "+lhs")
+ ]
+ where
+ t n f = test n ["--wrap=preserve", "-r", "native", "-s", "-w", f]
+ "lhs-test.native" ("lhs-test" <.> f)
+
+lhsReaderTest :: String -> TestTree
+lhsReaderTest format =
+ test "lhs" ["-r", format, "-w", "native"]
+ ("lhs-test" <.> format) norm
+ where norm = if format == "markdown+lhs"
+ then "lhs-test-markdown.native"
+ else "lhs-test.native"
+
+writerTests :: String -> [TestTree]
+writerTests format
+ = [ test "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format)
+ , test "tables" opts "tables.native" ("tables" <.> format)
+ ]
+ where
+ opts = ["-r", "native", "-w", format, "--columns=78",
+ "--variable", "pandoc-version="]
+
+s5WriterTest :: String -> [String] -> String -> TestTree
+s5WriterTest modifier opts format
+ = test (format ++ " writer (" ++ modifier ++ ")")
+ (["-r", "native", "-w", format] ++ opts)
+ "s5.native" ("s5-" ++ modifier <.> "html")
+
+fb2WriterTest :: String -> [String] -> String -> String -> TestTree
+fb2WriterTest title opts inputfile normfile =
+ testWithNormalize (ignoreBinary . formatXML)
+ title (["-t", "fb2"]++opts) inputfile normfile
+ where
+ formatXML xml = splitTags $ zip xml (drop 1 xml)
+ splitTags [] = []
+ splitTags [end] = fst end : snd end : []
+ splitTags (('>','<'):rest) = ">\n" ++ splitTags rest
+ splitTags ((c,_):rest) = c : splitTags rest
+ ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines
+ startsWith tag str = all (uncurry (==)) $ zip tag str
+
+-- | Run a test without normalize function, return True if test passed.
+test :: String -- ^ Title of test
+ -> [String] -- ^ Options to pass to pandoc
+ -> String -- ^ Input filepath
+ -> FilePath -- ^ Norm (for test results) filepath
+ -> TestTree
+test = testWithNormalize id
+
+-- | Run a test with normalize function, return True if test passed.
+testWithNormalize :: (String -> String) -- ^ Normalize function for output
+ -> String -- ^ Title of test
+ -> [String] -- ^ Options to pass to pandoc
+ -> String -- ^ Input filepath
+ -> FilePath -- ^ Norm (for test results) filepath
+ -> TestTree
+testWithNormalize normalizer testname opts inp norm =
+ goldenTest testname getExpected getActual
+ (compareValues norm options) updateGolden
+ where getExpected = normalizer <$> readFile' norm
+ getActual =
+ withTempFile "." "pandoc-test" $ \outputPath hOut -> do
+ withTempFile "." "pandoc-test" $ \errorPath hErr -> do
+ pandocPath <- findPandoc
+ let mbDynlibDir = findDynlibDir (reverse $
+ splitDirectories pandocPath)
+ let dynlibEnv = case mbDynlibDir of
+ Nothing -> []
+ Just d -> [("DYLD_LIBRARY_PATH", d),
+ ("LD_LIBRARY_PATH", d)]
+ let env = dynlibEnv ++
+ [("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./"),
+ ("pandoc_datadir","..")]
+ ph <- runProcess pandocPath options Nothing
+ (Just env) Nothing (Just hOut) (Just hErr)
+ ec <- waitForProcess ph
+ if ec == ExitSuccess
+ then
+ -- filter \r so the tests will work on Windows machines
+ (filter (/='\r') . normalizer) <$> readFile' outputPath
+ else do
+ errcontents <- UTF8.readFile errorPath
+ fail $ "Pandoc failed with " ++ show ec ++
+ if null errcontents
+ then ""
+ else '\n':errcontents
+ updateGolden = UTF8.writeFile norm
+ options = ["--quiet"] ++ [inp] ++ opts
+
+compareValues :: FilePath -> [String] -> String -> String -> IO (Maybe String)
+compareValues norm options expected actual = do
+ pandocPath <- findPandoc
+ let cmd = pandocPath ++ " " ++ unwords options
+ let dash = replicate 72 '-'
+ let diff = getDiff (lines actual) (lines expected)
+ if expected == actual
+ then return Nothing
+ else return $ Just $
+ '\n' : dash ++
+ "\n--- " ++ norm ++
+ "\n+++ " ++ cmd ++ "\n" ++
+ showDiff (1,1) diff ++ dash
+
+findDynlibDir :: [FilePath] -> Maybe FilePath
+findDynlibDir [] = Nothing
+findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
+findDynlibDir (_:xs) = findDynlibDir xs
+
diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs
new file mode 100644
index 000000000..3f60a523d
--- /dev/null
+++ b/test/Tests/Readers/Creole.hs
@@ -0,0 +1,286 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Creole (tests) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+creole :: Text -> Pandoc
+creole = purely $ readCreole def{ readerStandalone = True }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test creole
+
+tests :: [TestTree]
+tests = [
+ testGroup "Basic Text Formatting" [
+ "bold, single line, fully delimited" =:
+ "only **bold** is bold"
+ =?> para ("only " <> strong "bold" <> " is bold")
+ , "italics, single line, fully delimited" =:
+ "only //this// is in italics"
+ =?> para ("only " <> emph "this" <> " is in italics")
+ , "bold in italics, fully delimited" =:
+ "//**this**// is in bold italics"
+ =?> para (emph (strong "this") <> " is in bold italics")
+ , "italics in bold, fully delimited" =:
+ "**//this//** is in bold italics"
+ =?> para (strong (emph "this") <> " is in bold italics")
+
+ , "escape bold marker" =:
+ "~**not bold" =?> para "**not bold"
+ , "escape italics marker" =:
+ "~//not in italics" =?> para "//not in italics"
+
+ , "inline nowiki, simple" =:
+ "this is {{{**not** ~interpreted}}} at all"
+ =?> para ("this is " <> code "**not** ~interpreted" <> " at all")
+ , "inline nowiki, curly braces inside" =:
+ "this is {{{{{{//including// some `}' chars}}}}}}"
+ =?> para ("this is " <> code "{{{//including// some `}' chars}}}")
+
+ , "placeholder" =:
+ "foo <<<place holder>>> bar"
+ =?> para "foo bar"
+ , "placeholder escaped" =:
+ "foo ~<<<no place holder>>> bar"
+ =?> para "foo <<<no place holder>>> bar"
+ ]
+ , testGroup "Headers" [
+ "header level 1, no space, no trailing =" =:
+ "= Top-Level Header"
+ =?> header 1 (str "Top-Level Header")
+ , "header level 1, leading space, trailing =" =:
+ " = Top-Level Header = "
+ =?> header 1 (str "Top-Level Header")
+ , "header level 2, no space, no trailing =" =:
+ "== Second Level"
+ =?> header 2 (str "Second Level")
+ , "header level 2, leading space, no trailing =" =:
+ " == Second Level"
+ =?> header 2 (str "Second Level")
+ , "header level 3, no space, no trailing =" =:
+ "=== Third"
+ =?> header 3 (str "Third")
+ , "header level 3, no space, > 3 trailing =" =:
+ "=== Third ======="
+ =?> header 3 (str "Third")
+ , "header level 4, no space, no trailing =" =:
+ "==== Fourth Level Heading"
+ =?> header 4 (str "Fourth Level Heading")
+ , "header level 4, no space, < 4 trailing =" =:
+ "==== Fourth Level Heading =="
+ =?> header 4 (str "Fourth Level Heading")
+ , "header level 5, no space, no trailing =" =:
+ "===== Fifth"
+ =?> header 5 (str "Fifth")
+ , "header level 6, no space, no trailing =" =:
+ "====== Sixth"
+ =?> header 6 (str "Sixth")
+ ]
+ , testGroup "Paragraphs" [
+ "paragraphs: multiple, one line" =:
+ "first line\n\nanother line\n"
+ =?> para "first line" <> para "another line"
+ ]
+ , testGroup "Lists" [
+ "unordered list, two entries, one separating space" =:
+ "* foo\n* bar"
+ =?> bulletList [ plain "foo", plain "bar" ]
+ , "unordered list, three entries, one separating space" =:
+ "* foo\n* bar\n* baz"
+ =?> bulletList [ plain "foo", plain "bar", plain "baz" ]
+ , "para followed by, unordered list, two entries, one separating space" =:
+ "blubber\n* foo\n* bar"
+ =?> para "blubber" <> bulletList [ plain "foo", plain "bar" ]
+ , "nested unordered list, one separating space" =:
+ "* foo\n** bar\n** baz\n* blubb"
+ =?> bulletList [ plain "foo"
+ <> bulletList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "nested many unordered lists, one separating space" =:
+ ("* foo\n** bar\n*** third\n*** third two\n** baz\n*** third again\n"
+ <> "**** fourth\n***** fith\n* blubb")
+ =?> bulletList [ plain "foo"
+ <> bulletList [ plain "bar"
+ <> bulletList [ plain "third"
+ , plain "third two"]
+ , plain "baz"
+ <> bulletList [ plain "third again"
+ <> bulletList [
+ plain "fourth"
+ <> bulletList [
+ plain "fith"
+ ]
+ ]
+ ]
+ ]
+ , plain "blubb" ]
+ , "nested unordered list, mixed separating space" =:
+ "*foo\n ** bar\n **baz\n * blubb"
+ =?> bulletList [ plain "foo"
+ <> bulletList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "nested unordered list, one separating space, trailing space" =:
+ "* foo \n** bar \n** baz \n* blubb "
+ =?> bulletList [ plain "foo"
+ <> bulletList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "ordered list, two entries, one separating space" =:
+ "# foo\n# bar"
+ =?> orderedList [ plain "foo", plain "bar" ]
+ , "ordered list, three entries, one separating space" =:
+ "# foo\n# bar\n# baz"
+ =?> orderedList [ plain "foo", plain "bar", plain "baz" ]
+ , "para followed by, ordered list, two entries, one separating space" =:
+ "blubber\n# foo\n# bar"
+ =?> para "blubber" <> orderedList [ plain "foo", plain "bar" ]
+ , "nested ordered list, one separating space" =:
+ "# foo\n## bar\n## baz\n# blubb"
+ =?> orderedList [ plain "foo"
+ <> orderedList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "nested ordered list, one separating space, trailing space" =:
+ "# foo \n## bar \n## baz \n# blubb "
+ =?> orderedList [ plain "foo"
+ <> orderedList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "nested many ordered lists, one separating space" =:
+ ("# foo\n## bar\n### third\n### third two\n## baz\n### third again\n"
+ <> "#### fourth\n##### fith\n# blubb")
+ =?> orderedList [ plain "foo"
+ <> orderedList [ plain "bar"
+ <> orderedList [ plain "third"
+ , plain "third two"]
+ , plain "baz"
+ <> orderedList [ plain "third again"
+ <> orderedList [
+ plain "fourth"
+ <> orderedList [
+ plain "fith"
+ ]
+ ]
+ ]
+ ]
+ , plain "blubb" ]
+ , "nested ordered list, mixed separating space" =:
+ "#foo\n ## bar\n ##baz\n # blubb"
+ =?> orderedList [ plain "foo"
+ <> orderedList [ plain "bar", plain "baz" ]
+ , plain "blubb" ]
+ , "mixed nested ordered and unordered lists, one separating space" =:
+ ("# foo\n** bar\n### third\n### third two\n** baz\n### third again\n"
+ <> "#### fourth\n***** fith\n# blubb")
+ =?> orderedList [ plain "foo"
+ <> bulletList [ plain "bar"
+ <> orderedList [ plain "third"
+ , plain "third two"]
+ , plain "baz"
+ <> orderedList [ plain "third again"
+ <> orderedList [
+ plain "fourth"
+ <> bulletList [
+ plain "fith"
+ ]
+ ]
+ ]
+ ]
+ , plain "blubb" ]
+ ]
+ , testGroup "NoWiki" [
+ "quoted block, simple" =:
+ "{{{\nfoo bar\n //baz//\n}}}"
+ =?> codeBlock "foo bar\n //baz//"
+ , "quoted block, curly bracket exception" =:
+ "{{{\nfoo bar\n }}}\nbaz\n }}}\n}}}"
+ =?> codeBlock "foo bar\n }}}\nbaz\n}}}"
+ , "forced line breaks" =:
+ "{{{no break!\\\\here}}} but a break\\\\here!"
+ =?> para (code "no break!\\\\here" <> " but a break"
+ <> linebreak <> "here!"),
+ "quoted block, after trailing white space" =:
+ "this is a paragraph \n{{{\nfoo bar\n //baz//\n}}}"
+ =?> para "this is a paragraph" <> codeBlock "foo bar\n //baz//"
+ ]
+ , testGroup "Images and Links" [
+ "image simple" =:
+ "{{foo.png}}" =?> para (image "foo.png" "" (str ""))
+ , "image with alt text" =:
+ "Image of a bar: {{/path/to/bar.png|A Bar}} look at it!"
+ =?> para ("Image of a bar: "
+ <> image "/path/to/bar.png" "" (str "A Bar") <> " look at it!")
+
+ , "auto link" =:
+ "foo http://foo.example.com/bar/baz.html bar"
+ =?> para ("foo "
+ <> link "http://foo.example.com/bar/baz.html" ""
+ (str "http://foo.example.com/bar/baz.html")
+ <> " bar")
+ , "escaped auto link" =:
+ "foo ~http://foo.example.com/bar/baz.html bar"
+ =?> para "foo http://foo.example.com/bar/baz.html bar"
+ , "wiki link simple" =:
+ "foo [[http://foo.example.com/foo.png]] bar"
+ =?> para ("foo "
+ <> link "http://foo.example.com/foo.png" ""
+ (str "http://foo.example.com/foo.png")
+ <> " bar")
+ , "wiki link with name" =:
+ "foo [[http://foo.example.com/foo.png|my link]] bar"
+ =?> para ("foo "
+ <> link "http://foo.example.com/foo.png" ""
+ (str "my link")
+ <> " bar")
+ , "image link" =:
+ "[[http://foo.example.com/|{{foo.png}}]]"
+ =?> para (link "http://foo.example.com/" "" (image "foo.png" "" (str "")))
+ ]
+ , testGroup "Table" [
+ "Table with Header" =:
+ T.unlines [ "|= Foo |= Bar |= Baz |"
+ , "| One | Two | Three |"
+ , "| 1 | 2 | 3 |"
+ , "| A | B | C |"
+ ]
+ =?> simpleTable
+ [plain "Foo", plain "Bar" , plain "Baz"]
+ [[plain "One", plain "Two" , plain "Three"]
+ ,[plain "1", plain "2" , plain "3"]
+ ,[plain "A", plain "B" , plain "C"]]
+ , "Table without Header" =:
+ T.unlines [ "| One | Two | Three |"
+ , "| 1 | 2 | 3 |"
+ , "| A | B | C |"
+ ]
+ =?> simpleTable [mempty]
+ [[plain "One", plain "Two" , plain "Three"]
+ ,[plain "1", plain "2" , plain "3"]
+ ,[plain "A", plain "B" , plain "C"]]
+ , "Table without Header, no markers at line ends" =:
+ T.unlines [ "| One | Two | Three"
+ , "| 1 | 2 | 3"
+ , "| A | B | C "
+ ]
+ =?> simpleTable [mempty]
+ [[plain "One", plain "Two" , plain "Three"]
+ ,[plain "1", plain "2" , plain "3"]
+ ,[plain "A", plain "B" , plain "C"]]
+ , "Table with Header, with formatting" =:
+ T.unlines [ "|= **Foo** |= **Bar** |= **Baz** |"
+ , "|//one// element |//second// elt|Three |"
+ , "| {{{1}}} | {{{{}}}} | [[link]] |"
+ ]
+ =?> simpleTable
+ [plain $ strong "Foo", plain $ strong "Bar" , plain $ strong "Baz"]
+ [[plain (emph "one" <> " element"), plain (emph "second" <> " elt")
+ ,plain "Three"]
+ ,[plain $ code "1", plain $ code "{}"
+ ,plain $ link "link" "" (str "link")]]
+ ]
+ ]
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
new file mode 100644
index 000000000..0ba765c93
--- /dev/null
+++ b/test/Tests/Readers/Docx.hs
@@ -0,0 +1,401 @@
+module Tests.Readers.Docx (tests) where
+
+import Codec.Archive.Zip
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as B
+import qualified Data.Map as M
+import qualified Data.Text as T
+import Data.Maybe
+import System.IO.Unsafe
+import Test.Tasty
+import Test.Tasty.HUnit
+import Tests.Helpers
+import Text.Pandoc
+import qualified Text.Pandoc.Class as P
+import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
+import Text.Pandoc.UTF8 as UTF8
+
+-- We define a wrapper around pandoc that doesn't normalize in the
+-- tests. Since we do our own normalization, we want to make sure
+-- we're doing it right.
+
+data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
+ deriving Show
+
+noNorm :: Pandoc -> NoNormPandoc
+noNorm = NoNormPandoc
+
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "docx" }
+
+instance ToString NoNormPandoc where
+ toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ where s = case d of
+ NoNormPandoc (Pandoc (Meta m) _)
+ | M.null m -> Nothing
+ | otherwise -> Just "" -- need this to get meta output
+
+instance ToPandoc NoNormPandoc where
+ toPandoc = unNoNorm
+
+compareOutput :: ReaderOptions
+ -> FilePath
+ -> FilePath
+ -> IO (NoNormPandoc, NoNormPandoc)
+compareOutput opts docxFile nativeFile = do
+ df <- B.readFile docxFile
+ nf <- UTF8.toText <$> BS.readFile nativeFile
+ p <- runIOorExplode $ readDocx opts df
+ df' <- runIOorExplode $ readNative def nf
+ return (noNorm p, noNorm df')
+
+testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO TestTree
+testCompareWithOptsIO opts name docxFile nativeFile = do
+ (dp, np) <- compareOutput opts docxFile nativeFile
+ return $ test id name (dp, np)
+
+testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> TestTree
+testCompareWithOpts opts name docxFile nativeFile =
+ unsafePerformIO $ testCompareWithOptsIO opts name docxFile nativeFile
+
+testCompare :: String -> FilePath -> FilePath -> TestTree
+testCompare = testCompareWithOpts defopts
+
+testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO TestTree
+testForWarningsWithOptsIO opts name docxFile expected = do
+ df <- B.readFile docxFile
+ logs <- runIOorExplode $ setVerbosity ERROR >> readDocx opts df >> P.getLog
+ let warns = [m | DocxParserWarning m <- logs]
+ return $ test id name (unlines warns, unlines expected)
+
+testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> TestTree
+testForWarningsWithOpts opts name docxFile expected =
+ unsafePerformIO $ testForWarningsWithOptsIO opts name docxFile expected
+
+-- testForWarnings :: String -> FilePath -> [String] -> TestTree
+-- testForWarnings = testForWarningsWithOpts defopts
+
+getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
+getMedia archivePath mediaPath = do
+ zf <- B.readFile archivePath >>= return . toArchive
+ return $ findEntryByPath ("word/" ++ mediaPath) zf >>= (Just . fromEntry)
+
+compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
+compareMediaPathIO mediaPath mediaBag docxPath = do
+ docxMedia <- getMedia docxPath mediaPath
+ let mbBS = case lookupMedia mediaPath mediaBag of
+ Just (_, bs) -> bs
+ Nothing -> error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")
+ docxBS = fromMaybe (error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")) docxMedia
+ return $ mbBS == docxBS
+
+compareMediaBagIO :: FilePath -> IO Bool
+compareMediaBagIO docxFile = do
+ df <- B.readFile docxFile
+ mb <- runIOorExplode $ readDocx defopts df >> P.getMediaBag
+ bools <- mapM
+ (\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
+ (mediaDirectory mb)
+ return $ and bools
+
+testMediaBagIO :: String -> FilePath -> IO TestTree
+testMediaBagIO name docxFile = do
+ outcome <- compareMediaBagIO docxFile
+ return $ testCase name (assertBool
+ ("Media didn't match media bag in file " ++ docxFile)
+ outcome)
+
+testMediaBag :: String -> FilePath -> TestTree
+testMediaBag name docxFile = unsafePerformIO $ testMediaBagIO name docxFile
+
+tests :: [TestTree]
+tests = [ testGroup "inlines"
+ [ testCompare
+ "font formatting"
+ "docx/inline_formatting.docx"
+ "docx/inline_formatting.native"
+ , testCompare
+ "font formatting with character styles"
+ "docx/char_styles.docx"
+ "docx/char_styles.native"
+ , testCompare
+ "hyperlinks"
+ "docx/links.docx"
+ "docx/links.native"
+ , testCompare
+ "hyperlinks in <w:instrText> tag"
+ "docx/instrText_hyperlink.docx"
+ "docx/instrText_hyperlink.native"
+ , testCompare
+ "inline image"
+ "docx/image.docx"
+ "docx/image_no_embed.native"
+ , testCompare
+ "VML image"
+ "docx/image_vml.docx"
+ "docx/image_vml.native"
+ , testCompare
+ "inline image in links"
+ "docx/inline_images.docx"
+ "docx/inline_images.native"
+ , testCompare
+ "handling unicode input"
+ "docx/unicode.docx"
+ "docx/unicode.native"
+ , testCompare
+ "literal tabs"
+ "docx/tabs.docx"
+ "docx/tabs.native"
+ , testCompare
+ "special punctuation"
+ "docx/special_punctuation.docx"
+ "docx/special_punctuation.native"
+ , testCompare
+ "normalizing inlines"
+ "docx/normalize.docx"
+ "docx/normalize.native"
+ , testCompare
+ "normalizing inlines deep inside blocks"
+ "docx/deep_normalize.docx"
+ "docx/deep_normalize.native"
+ , testCompare
+ "move trailing spaces outside of formatting"
+ "docx/trailing_spaces_in_formatting.docx"
+ "docx/trailing_spaces_in_formatting.native"
+ , testCompare
+ "inline code (with VerbatimChar style)"
+ "docx/inline_code.docx"
+ "docx/inline_code.native"
+ , testCompare
+ "inline code in subscript and superscript"
+ "docx/verbatim_subsuper.docx"
+ "docx/verbatim_subsuper.native"
+ , testCompare
+ "inlines inside of Structured Document Tags"
+ "docx/sdt_elements.docx"
+ "docx/sdt_elements.native"
+ , testCompare
+ "nested Structured Document Tags"
+ "docx/nested_sdt.docx"
+ "docx/nested_sdt.native"
+ , testCompare
+ "remove anchor spans with nothing pointing to them"
+ "docx/unused_anchors.docx"
+ "docx/unused_anchors.native"
+ , testCompare
+ "collapse overlapping targets (anchor spans)"
+ "docx/overlapping_targets.docx"
+ "docx/overlapping_targets.native"
+ ]
+ , testGroup "blocks"
+ [ testCompare
+ "headers"
+ "docx/headers.docx"
+ "docx/headers.native"
+ , testCompare
+ "headers already having auto identifiers"
+ "docx/already_auto_ident.docx"
+ "docx/already_auto_ident.native"
+ , testCompare
+ "avoid zero-level headers"
+ "docx/0_level_headers.docx"
+ "docx/0_level_headers.native"
+ , testCompare
+ "nested anchor spans in header"
+ "docx/nested_anchors_in_header.docx"
+ "docx/nested_anchors_in_header.native"
+ , testCompare
+ "single numbered item not made into list"
+ "docx/numbered_header.docx"
+ "docx/numbered_header.native"
+ , testCompare
+ "enumerated headers not made into numbered list"
+ "docx/enumerated_headings.docx"
+ "docx/enumerated_headings.native"
+ , testCompare
+ "i18n blocks (headers and blockquotes)"
+ "docx/i18n_blocks.docx"
+ "docx/i18n_blocks.native"
+ , testCompare
+ "lists"
+ "docx/lists.docx"
+ "docx/lists.native"
+ , testCompare
+ "lists continuing after interruption"
+ "docx/lists_continuing.docx"
+ "docx/lists_continuing.native"
+ , testCompare
+ "lists restarting after interruption"
+ "docx/lists_restarting.docx"
+ "docx/lists_restarting.native"
+ , testCompare
+ "definition lists"
+ "docx/definition_list.docx"
+ "docx/definition_list.native"
+ , testCompare
+ "custom defined lists in styles"
+ "docx/german_styled_lists.docx"
+ "docx/german_styled_lists.native"
+ , testCompare
+ "user deletes bullet after list item (=> part of item par)"
+ "docx/dummy_item_after_list_item.docx"
+ "docx/dummy_item_after_list_item.native"
+ , testCompare
+ "user deletes bullet after par (=> new par)"
+ "docx/dummy_item_after_paragraph.docx"
+ "docx/dummy_item_after_paragraph.native"
+ , testCompare
+ "footnotes and endnotes"
+ "docx/notes.docx"
+ "docx/notes.native"
+ , testCompare
+ "links in footnotes and endnotes"
+ "docx/link_in_notes.docx"
+ "docx/link_in_notes.native"
+ , testCompare
+ "blockquotes (parsing indent as blockquote)"
+ "docx/block_quotes.docx"
+ "docx/block_quotes_parse_indent.native"
+ , testCompare
+ "hanging indents"
+ "docx/hanging_indent.docx"
+ "docx/hanging_indent.native"
+ , testCompare
+ "tables"
+ "docx/tables.docx"
+ "docx/tables.native"
+ , testCompare
+ "tables with lists in cells"
+ "docx/table_with_list_cell.docx"
+ "docx/table_with_list_cell.native"
+ , testCompare
+ "tables with one row"
+ "docx/table_one_row.docx"
+ "docx/table_one_row.native"
+ , testCompare
+ "tables with variable width"
+ "docx/table_variable_width.docx"
+ "docx/table_variable_width.native"
+ , testCompare
+ "code block"
+ "docx/codeblock.docx"
+ "docx/codeblock.native"
+ , testCompare
+ "dropcap paragraphs"
+ "docx/drop_cap.docx"
+ "docx/drop_cap.native"
+ ]
+ , testGroup "track changes"
+ [ testCompare
+ "insertion (default)"
+ "docx/track_changes_insertion.docx"
+ "docx/track_changes_insertion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "insert insertion (accept)"
+ "docx/track_changes_insertion.docx"
+ "docx/track_changes_insertion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "remove insertion (reject)"
+ "docx/track_changes_insertion.docx"
+ "docx/track_changes_insertion_reject.native"
+ , testCompare
+ "deletion (default)"
+ "docx/track_changes_deletion.docx"
+ "docx/track_changes_deletion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "remove deletion (accept)"
+ "docx/track_changes_deletion.docx"
+ "docx/track_changes_deletion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "insert deletion (reject)"
+ "docx/track_changes_deletion.docx"
+ "docx/track_changes_deletion_reject.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "keep insertion (all)"
+ "docx/track_changes_deletion.docx"
+ "docx/track_changes_deletion_all.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "keep deletion (all)"
+ "docx/track_changes_deletion.docx"
+ "docx/track_changes_deletion_all.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "move text (accept)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "move text (reject)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_reject.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "move text (all)"
+ "docx/track_changes_move.docx"
+ "docx/track_changes_move_all.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "comments (accept -- no comments)"
+ "docx/comments.docx"
+ "docx/comments_no_comments.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "comments (reject -- comments)"
+ "docx/comments.docx"
+ "docx/comments_no_comments.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "comments (all comments)"
+ "docx/comments.docx"
+ "docx/comments.native"
+ , testCompareWithOpts def{readerTrackChanges=AcceptChanges}
+ "paragraph insertion/deletion (accept)"
+ "docx/paragraph_insertion_deletion.docx"
+ "docx/paragraph_insertion_deletion_accept.native"
+ , testCompareWithOpts def{readerTrackChanges=RejectChanges}
+ "paragraph insertion/deletion (reject)"
+ "docx/paragraph_insertion_deletion.docx"
+ "docx/paragraph_insertion_deletion_reject.native"
+ , testCompareWithOpts def{readerTrackChanges=AllChanges}
+ "paragraph insertion/deletion (all)"
+ "docx/paragraph_insertion_deletion.docx"
+ "docx/paragraph_insertion_deletion_all.native"
+ , testForWarningsWithOpts def{readerTrackChanges=AcceptChanges}
+ "comment warnings (accept -- no warnings)"
+ "docx/comments_warning.docx"
+ []
+ , testForWarningsWithOpts def{readerTrackChanges=RejectChanges}
+ "comment warnings (reject -- no warnings)"
+ "docx/comments_warning.docx"
+ []
+ , testForWarningsWithOpts def{readerTrackChanges=AllChanges}
+ "comment warnings (all)"
+ "docx/comments_warning.docx"
+ ["Docx comment 1 will not retain formatting"]
+ ]
+ , testGroup "media"
+ [ testMediaBag
+ "image extraction"
+ "docx/image.docx"
+ ]
+ , testGroup "custom styles"
+ [ testCompare
+ "custom styles (`+styles`) not enabled (default)"
+ "docx/custom-style-reference.docx"
+ "docx/custom-style-no-styles.native"
+ , testCompareWithOpts
+ def{readerExtensions=extensionsFromList [Ext_styles]}
+ "custom styles (`+styles`) enabled"
+ "docx/custom-style-reference.docx"
+ "docx/custom-style-with-styles.native"
+ ]
+ , testGroup "metadata"
+ [ testCompareWithOpts def{readerStandalone=True}
+ "metadata fields"
+ "docx/metadata.docx"
+ "docx/metadata.native"
+ , testCompareWithOpts def{readerStandalone=True}
+ "stop recording metadata with normal text"
+ "docx/metadata_after_normal.docx"
+ "docx/metadata_after_normal.native"
+ ]
+
+ ]
diff --git a/test/Tests/Readers/EPUB.hs b/test/Tests/Readers/EPUB.hs
new file mode 100644
index 000000000..1337a9c11
--- /dev/null
+++ b/test/Tests/Readers/EPUB.hs
@@ -0,0 +1,40 @@
+module Tests.Readers.EPUB (tests) where
+
+import qualified Data.ByteString.Lazy as BL
+import Test.Tasty
+import Test.Tasty.HUnit
+import qualified Text.Pandoc.Class as P
+import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
+import Text.Pandoc.Options
+import Text.Pandoc.Readers.EPUB
+
+getMediaBag :: FilePath -> IO MediaBag
+getMediaBag fp = do
+ bs <- BL.readFile fp
+ P.runIOorExplode $ do
+ readEPUB def bs
+ P.getMediaBag
+
+testMediaBag :: FilePath -> [(String, String, Int)] -> IO ()
+testMediaBag fp bag = do
+ actBag <- mediaDirectory <$> getMediaBag fp
+ assertBool (show "MediaBag did not match:\nExpected: "
+ ++ show bag
+ ++ "\nActual: "
+ ++ show actBag)
+ (actBag == bag)
+
+featuresBag :: [(String, String, Int)]
+featuresBag = [("img/check.gif","image/gif",1340)
+ ,("img/check.jpg","image/jpeg",2661)
+ ,("img/check.png","image/png",2815)
+ ,("img/multiscripts_and_greek_alphabet.png","image/png",10060)
+ ]
+
+tests :: [TestTree]
+tests =
+ [ testGroup "EPUB Mediabag"
+ [ testCase "features bag"
+ (testMediaBag "epub/img.epub" featuresBag)
+ ]
+ ]
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
new file mode 100644
index 000000000..70f33d2b2
--- /dev/null
+++ b/test/Tests/Readers/HTML.hs
@@ -0,0 +1,54 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.HTML (tests) where
+
+import Data.Text (Text)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+html :: Text -> Pandoc
+html = purely $ readHtml def
+
+htmlNativeDivs :: Text -> Pandoc
+htmlNativeDivs = purely $ readHtml def { readerExtensions = enableExtension Ext_native_divs $ readerExtensions def }
+
+tests :: [TestTree]
+tests = [ testGroup "base tag"
+ [ test html "simple" $
+ "<head><base href=\"http://www.w3schools.com/images/foo\" ></head><body><img src=\"stickman.gif\" alt=\"Stickman\"></head>" =?>
+ plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman"))
+ , test html "slash at end of base" $
+ "<head><base href=\"http://www.w3schools.com/images/\" ></head><body><img src=\"stickman.gif\" alt=\"Stickman\"></head>" =?>
+ plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman"))
+ , test html "slash at beginning of href" $
+ "<head><base href=\"http://www.w3schools.com/images/\" ></head><body><img src=\"/stickman.gif\" alt=\"Stickman\"></head>" =?>
+ plain (image "http://www.w3schools.com/stickman.gif" "" (text "Stickman"))
+ , test html "absolute URL" $
+ "<head><base href=\"http://www.w3schools.com/images/\" ></head><body><img src=\"http://example.com/stickman.gif\" alt=\"Stickman\"></head>" =?>
+ plain (image "http://example.com/stickman.gif" "" (text "Stickman"))
+ ]
+ , testGroup "anchors"
+ [ test html "anchor without href" $ "<a name=\"anchor\"/>" =?>
+ plain (spanWith ("anchor",[],[]) mempty)
+ ]
+ , testGroup "lang"
+ [ test html "lang on <html>" $ "<html lang=\"es\">hola" =?>
+ setMeta "lang" (text "es") (doc (plain (text "hola")))
+ , test html "xml:lang on <html>" $ "<html xmlns=\"http://www.w3.org/1999/xhtml\" xml:lang=\"es\"><head></head><body>hola</body></html>" =?>
+ setMeta "lang" (text "es") (doc (plain (text "hola")))
+ ]
+ , testGroup "main"
+ [ test htmlNativeDivs "<main> becomes <div role=main>" $ "<main>hello</main>" =?>
+ doc (divWith ("", [], [("role", "main")]) (plain (text "hello")))
+ , test htmlNativeDivs "<main role=X> becomes <div role=X>" $ "<main role=foobar>hello</main>" =?>
+ doc (divWith ("", [], [("role", "foobar")]) (plain (text "hello")))
+ , test htmlNativeDivs "<main> has attributes preserved" $ "<main id=foo class=bar data-baz=qux>hello</main>" =?>
+ doc (divWith ("foo", ["bar"], [("role", "main"), ("data-baz", "qux")]) (plain (text "hello")))
+ , test htmlNativeDivs "<main> closes <p>" $ "<p>hello<main>main content</main>" =?>
+ doc (para (text "hello") <> divWith ("", [], [("role", "main")]) (plain (text "main content")))
+ , test htmlNativeDivs "<main> followed by text" $ "<main>main content</main>non-main content" =?>
+ doc (divWith ("", [], [("role", "main")]) (plain (text "main content")) <> plain (text "non-main content"))
+ ]
+ ]
diff --git a/test/Tests/Readers/JATS.hs b/test/Tests/Readers/JATS.hs
new file mode 100644
index 000000000..5c7dfa77c
--- /dev/null
+++ b/test/Tests/Readers/JATS.hs
@@ -0,0 +1,116 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.JATS (tests) where
+
+import Data.Text (Text)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+jats :: Text -> Pandoc
+jats = purely $ readJATS def
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ test jats "basic" $ "<p>\n <monospace>@&amp;</monospace>\n</p>" =?> para (code "@&")
+ , test jats "lang" $ "<p>\n <code language=\"c\">@&amp;</code>\n</p>" =?> para (codeWith ("", ["c"], []) "@&")
+ ]
+ , testGroup "block code"
+ [ test jats "basic" $ "<preformat>@&amp;</preformat>" =?> codeBlock "@&"
+ , test jats "lang" $ "<code language=\"c\">@&amp;</code>" =?> codeBlockWith ("", ["c"], []) "@&"
+ ]
+ , testGroup "images"
+ [ test jats "basic" $ "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ =?> para (image "/url" "title" mempty)
+ ]
+ , test jats "bullet list" $
+ "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ first\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ second\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ third\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \</list>"
+ =?> bulletList [ para $ text "first"
+ , para $ text "second"
+ , para $ text "third"
+ ]
+ , testGroup "definition lists"
+ [ test jats "with internal link" $
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term>\n\
+ \ <xref alt=\"testing\" rid=\"go\">testing</xref>\n\
+ \ </term>\n\
+ \ <def>\n\
+ \ <p>\n\
+ \ hi there\n\
+ \ </p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ =?> definitionList [(link "#go" "" (str "testing"),
+ [para (text "hi there")])]
+ ]
+ , testGroup "math"
+ [ test jats "escape |" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{x\\}}")
+ , test jats "tex-math only" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{x\\}}")
+ , test jats "math ml only" $
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ =?> para (math "\\sigma|_{\\{ x\\}}")
+ ]
+ , testGroup "headers"
+-- TODO fix footnotes in headers
+-- [ test jats "unnumbered header" $
+-- "<sec>\n\
+-- \ <title>Header 1<fn>\n\
+-- \ <p>\n\
+-- \ note\n\
+-- \ </p>\n\
+-- \ </fn></title>\n\
+-- \</sec>"
+-- =?> header 1
+-- (text "Header 1" <> note (plain $ text "note"))
+ [ test jats "unnumbered sub header" $
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo2\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ =?> headerWith ("foo", [], []) 1
+ (text "Header")
+ <> headerWith ("foo2", [], []) 2
+ (text "Sub-Header")
+ , test jats "containing image" $
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ =?> header 1 (image "imgs/foo.jpg" "" mempty)
+ ]
+ ]
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
new file mode 100644
index 000000000..4396d550f
--- /dev/null
+++ b/test/Tests/Readers/LaTeX.hs
@@ -0,0 +1,341 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.LaTeX (tests) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Text.Pandoc.UTF8 as UTF8
+import Text.Pandoc.Readers.LaTeX (tokenize, untokenize)
+import Test.Tasty
+import Test.Tasty.HUnit
+import Test.Tasty.QuickCheck
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+latex :: Text -> Pandoc
+latex = purely $ readLaTeX def{
+ readerExtensions = getDefaultExtensions "latex" }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test latex
+
+simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
+simpleTable' aligns = table "" (zip aligns (repeat 0.0))
+ (map (const mempty) aligns)
+
+tokUntokRt :: String -> Bool
+tokUntokRt s = untokenize (tokenize "random" t) == t
+ where t = T.pack s
+
+tests :: [TestTree]
+tests = [ testGroup "tokenization"
+ [ testCase "tokenizer round trip on test case" $ do
+ orig <- T.pack <$> UTF8.readFile "../test/latex-reader.latex"
+ let new = untokenize $ tokenize "../test/latex-reader.latex"
+ orig
+ assertEqual "untokenize . tokenize is identity" orig new
+ , testProperty "untokenize . tokenize is identity" tokUntokRt
+ ]
+
+ , testGroup "basic"
+ [ "simple" =:
+ "word" =?> para "word"
+ , "space" =:
+ "some text" =?> para "some text"
+ , "emphasized" =:
+ "\\emph{emphasized}" =?> para (emph "emphasized")
+ ]
+
+ , testGroup "headers"
+ [ "level 1" =:
+ "\\section{header}" =?> headerWith ("header",[],[]) 1 "header"
+ , "level 2" =:
+ "\\subsection{header}" =?> headerWith ("header",[],[]) 2 "header"
+ , "level 3" =:
+ "\\subsubsection{header}" =?> headerWith ("header",[],[]) 3 "header"
+ , "emph" =:
+ "\\section{text \\emph{emph}}" =?>
+ headerWith ("text-emph",[],[]) 1 ("text" <> space <> emph "emph")
+ , "link" =:
+ "\\section{text \\href{/url}{link}}" =?>
+ headerWith ("text-link",[],[]) 1 ("text" <> space <> link "/url" "" "link")
+ ]
+
+ , testGroup "math"
+ [ "escaped $" =:
+ "$x=\\$4$" =?> para (math "x=\\$4")
+ ]
+
+ , testGroup "space and comments"
+ [ "blank lines + space at beginning" =:
+ "\n \n hi" =?> para "hi"
+ , "blank lines + space + comments" =:
+ "% my comment\n\n \n % another\n\nhi" =?> para "hi"
+ , "comment in paragraph" =:
+ "hi % this is a comment\nthere\n" =?>
+ para ("hi" <> softbreak <> "there")
+ ]
+
+ , testGroup "code blocks"
+ [ "identifier" =:
+ "\\begin{lstlisting}[label=test]\\end{lstlisting}" =?> codeBlockWith ("test", [], [("label","test")]) ""
+ , "no identifier" =:
+ "\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock ""
+ ]
+
+ , testGroup "tables"
+ [ "Single cell table" =:
+ "\\begin{tabular}{|l|}Test\\\\\\end{tabular}" =?>
+ simpleTable' [AlignLeft] [[plain "Test"]]
+ , "Multi cell table" =:
+ "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Multi line table" =:
+ T.unlines [ "\\begin{tabular}{|c|}"
+ , "One\\\\"
+ , "Two\\\\"
+ , "Three\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignCenter]
+ [[plain "One"], [plain "Two"], [plain "Three"]]
+ , "Empty table" =:
+ "\\begin{tabular}{}\\end{tabular}" =?>
+ simpleTable' [] []
+ , "Table with fixed column width" =:
+ "\\begin{tabular}{|p{5cm}r|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignLeft,AlignRight] [[plain "One", plain "Two"]]
+ , "Table with empty column separators" =:
+ "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with custom column separators" =:
+ T.unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}"
+ , "One&Two\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with vertical alignment argument" =:
+ "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]]
+ ]
+
+ , testGroup "citations"
+ [ natbibCitations
+ , biblatexCitations
+ ]
+
+ , testGroup "images"
+ [ "Basic image" =:
+ "\\includegraphics{foo.png}" =?>
+ para (image "foo.png" "" (text "image"))
+ , "Basic image with blank options" =:
+ "\\includegraphics[]{foo.png}" =?>
+ para (image "foo.png" "" (text "image"))
+ , "Image with both width and height" =:
+ "\\includegraphics[width=17cm,height=5cm]{foo.png}" =?>
+ para (imageWith ("", [], [("width", "17cm"), ("height", "5cm")]) "foo.png" "" "image")
+ , "Image with width and height and a bunch of other options" =:
+ "\\includegraphics[width=17cm,height=5cm,clip,keepaspectratio]{foo.png}" =?>
+ para (imageWith ("", [], [("width", "17cm"), ("height", "5cm")]) "foo.png" "" "image")
+ , "Image with just width" =:
+ "\\includegraphics[width=17cm]{foo.png}" =?>
+ para (imageWith ("", [], [("width", "17cm")]) "foo.png" "" "image")
+ , "Image with just height" =:
+ "\\includegraphics[height=17cm]{foo.png}" =?>
+ para (imageWith ("", [], [("height", "17cm")]) "foo.png" "" "image")
+ , "Image width relative to textsize" =:
+ "\\includegraphics[width=0.6\\textwidth]{foo.png}" =?>
+ para (imageWith ("", [], [("width", "60%")]) "foo.png" "" "image")
+ , "Image with options with spaces" =:
+ "\\includegraphics[width=12cm, height = 5cm]{foo.png}" =?>
+ para (imageWith ("", [], [("width", "12cm"), ("height", "5cm")]) "foo.png" "" "image")
+ ]
+
+ , let hex = ['0'..'9']++['a'..'f'] in
+ testGroup "Character Escapes"
+ [ "Two-character escapes" =:
+ mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?>
+ para (str ['\0'..'\255'])
+ , "One-character escapes" =:
+ mconcat ["^^" <> T.pack [i] | i <- hex] =?>
+ para (str $ ['p'..'y']++['!'..'&'])
+ ]
+ , testGroup "memoir scene breaks"
+ [ "plainbreak" =:
+ "hello\\plainbreak{2}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "plainbreak*" =:
+ "hello\\plainbreak*{2}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "fancybreak" =:
+ "hello\\fancybreak{b r e a k}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "fancybreak*" =:
+ "hello\\fancybreak*{b r e a k}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "plainfancybreak" =:
+ "hello\\plainfancybreak{4}{2}{b r e a k}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "plainfancybreak*" =:
+ "hello\\plainfancybreak*{4}{2}{b r e a k}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "pfbreak" =:
+ "hello\\pfbreak{}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ , "pfbreak*" =:
+ "hello\\pfbreak*{}goodbye" =?>
+ para (str "hello") <> horizontalRule <> para (str "goodbye")
+ ]
+ , testGroup "biblatex roman numerals"
+ [ "upper" =:
+ "number \\RN{12}" =?>
+ para (str "number" <> space <> str "XII")
+ , "lower" =:
+ "number \\Rn{29}" =?>
+ para (str "number" <> space <> str "xxix")
+ , "leading zero" =:
+ "\\Rn{014}" =?>
+ para (str "xiv")
+ , "surrounding spaces" =:
+ "number \\Rn{ 41 }" =?>
+ para (str "number" <> space <> str "xli")
+ , "zero" =:
+ "\\RN{0}" =?>
+ para (str "")
+ , "space then unbraced argument" =:
+ "\\RN 7 ok" =?>
+ para (str "VII" <> space <> str "ok")
+ , "space before braced argument" =:
+ "\\Rn {13}ok" =?>
+ para (str "xiiiok")
+ ]
+ , testGroup "polyglossia language spans"
+ [ "french" =:
+ "hello \\textfrench{bonjour}" =?>
+ para (str "hello" <> space <> spanWith ("", [], [("lang", "fr")]) (str "bonjour"))
+ , "nested" =:
+ "\\textfrench{quelle c'est \\textlatin{primus}?}" =?>
+ para (spanWith ("", [], [("lang", "fr")]) $
+ str "quelle" <> space <> str "c\8217est" <> space <>
+ spanWith ("", [], [("lang", "la")]) (str "primus") <> str "?")
+ , "with formatting" =:
+ "\\textgerman{wie \\emph{spaet} ist es?}" =?>
+ para (spanWith ("", [], [("lang", "de")]) $
+ str "wie" <> space <> emph (str "spaet") <> space <> str "ist" <> space <> str "es?")
+ , "language options" =:
+ "\\textgerman[variant=swiss]{hoechdeutsche}" =?>
+ para (spanWith ("", [], [("lang", "de-CH")]) $ str "hoechdeutsche")
+ , "unknown option fallback" =:
+ "\\textgerman[variant=moon]{ueberhoechdeutsche}" =?>
+ para (spanWith ("", [], [("lang", "de")]) $ str "ueberhoechdeutsche")
+ ]
+ ]
+
+baseCitation :: Citation
+baseCitation = Citation{ citationId = "item1"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+
+rt :: String -> Inlines
+rt = rawInline "latex"
+
+natbibCitations :: TestTree
+natbibCitations = testGroup "natbib"
+ [ "citet" =: "\\citet{item1}"
+ =?> para (cite [baseCitation] (rt "\\citet{item1}"))
+ , "suffix" =: "\\citet[p.~30]{item1}"
+ =?> para
+ (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}"))
+ , "suffix long" =: "\\citet[p.~30, with suffix]{item1}"
+ =?> para (cite [baseCitation{ citationSuffix =
+ toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}"))
+ , "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}"
+ =?> para (cite [baseCitation{ citationMode = AuthorInText }
+ ,baseCitation{ citationMode = SuppressAuthor
+ , citationSuffix = [Str "p.\160\&30"]
+ , citationId = "item2" }
+ ,baseCitation{ citationId = "item3"
+ , citationPrefix = [Str "see",Space,Str "also"]
+ , citationMode = NormalCitation }
+ ] (rt "\\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}"))
+ , "group" =: "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationPrefix = [Str "see"]
+ , citationSuffix = [Str "p.\160\&34\8211\&35"] }
+ ,baseCitation{ citationMode = NormalCitation
+ , citationId = "item3"
+ , citationPrefix = [Str "also"]
+ , citationSuffix = [Str "chap.",Space,Str "3"] }
+ ] (rt "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}"))
+ , "suffix and locator" =: "\\citep[pp.~33, 35--37, and nowhere else]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}"))
+ , "suffix only" =: "\\citep[and nowhere else]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationSuffix = toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}"))
+ , "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}"
+ =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\citeyearpar{item1}") <>
+ text ", and now Doe with a locator " <>
+ cite [baseCitation{ citationMode = SuppressAuthor
+ , citationSuffix = [Str "p.\160\&44"]
+ , citationId = "item2" }] (rt "\\citeyearpar[p.~44]{item2}"))
+ , "markup" =: "\\citep[\\emph{see}][p. \\textbf{32}]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationPrefix = [Emph [Str "see"]]
+ , citationSuffix = [Str "p.",Space,
+ Strong [Str "32"]] }] (rt "\\citep[\\emph{see}][p. \\textbf{32}]{item1}"))
+ ]
+
+biblatexCitations :: TestTree
+biblatexCitations = testGroup "biblatex"
+ [ "textcite" =: "\\textcite{item1}"
+ =?> para (cite [baseCitation] (rt "\\textcite{item1}"))
+ , "suffix" =: "\\textcite[p.~30]{item1}"
+ =?> para
+ (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}"))
+ , "suffix long" =: "\\textcite[p.~30, with suffix]{item1}"
+ =?> para (cite [baseCitation{ citationSuffix =
+ toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}"))
+ , "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}"
+ =?> para (cite [baseCitation{ citationMode = AuthorInText }
+ ,baseCitation{ citationMode = NormalCitation
+ , citationSuffix = [Str "p.\160\&30"]
+ , citationId = "item2" }
+ ,baseCitation{ citationId = "item3"
+ , citationPrefix = [Str "see",Space,Str "also"]
+ , citationMode = NormalCitation }
+ ] (rt "\\textcites{item1}[p.~30]{item2}[see also][]{item3}"))
+ , "group" =: "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationPrefix = [Str "see"]
+ , citationSuffix = [Str "p.\160\&34\8211\&35"] }
+ ,baseCitation{ citationMode = NormalCitation
+ , citationId = "item3"
+ , citationPrefix = [Str "also"]
+ , citationSuffix = [Str "chap.",Space,Str "3"] }
+ ] (rt "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}"))
+ , "suffix and locator" =: "\\autocite[pp.~33, 35--37, and nowhere else]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}"))
+ , "suffix only" =: "\\autocite[and nowhere else]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationSuffix = toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}"))
+ , "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}"
+ =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\autocite*{item1}") <>
+ text ", and now Doe with a locator " <>
+ cite [baseCitation{ citationMode = SuppressAuthor
+ , citationSuffix = [Str "p.\160\&44"]
+ , citationId = "item2" }] (rt "\\autocite*[p.~44]{item2}"))
+ , "markup" =: "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation
+ , citationPrefix = [Emph [Str "see"]]
+ , citationSuffix = [Str "p.",Space,
+ Strong [Str "32"]] }] (rt "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}"))
+ , "parencite" =: "\\parencite{item1}"
+ =?> para (cite [baseCitation{ citationMode = NormalCitation }] (rt "\\parencite{item1}"))
+ ]
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
new file mode 100644
index 000000000..1cd32b87d
--- /dev/null
+++ b/test/Tests/Readers/Markdown.hs
@@ -0,0 +1,462 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Markdown (tests) where
+
+import Data.Text (Text, unpack)
+import qualified Data.Text as T
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+markdown :: Text -> Pandoc
+markdown = purely $ readMarkdown def { readerExtensions =
+ disableExtension Ext_smart pandocExtensions }
+
+markdownSmart :: Text -> Pandoc
+markdownSmart = purely $ readMarkdown def { readerExtensions =
+ enableExtension Ext_smart pandocExtensions }
+
+markdownCDL :: Text -> Pandoc
+markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension
+ Ext_compact_definition_lists pandocExtensions }
+
+markdownGH :: Text -> Pandoc
+markdownGH = purely $ readMarkdown def {
+ readerExtensions = githubMarkdownExtensions }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test markdown
+
+testBareLink :: (Text, Inlines) -> TestTree
+testBareLink (inp, ils) =
+ test (purely $ readMarkdown def{ readerExtensions =
+ extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] })
+ (unpack inp) (inp, doc $ para ils)
+
+autolink :: String -> Inlines
+autolink = autolinkWith nullAttr
+
+autolinkWith :: Attr -> String -> Inlines
+autolinkWith attr s = linkWith attr s "" (str s)
+
+bareLinkTests :: [(Text, Inlines)]
+bareLinkTests =
+ [ ("http://google.com is a search engine.",
+ autolink "http://google.com" <> " is a search engine.")
+ , ("<a href=\"http://foo.bar.baz\">http://foo.bar.baz</a>",
+ rawInline "html" "<a href=\"http://foo.bar.baz\">" <>
+ "http://foo.bar.baz" <> rawInline "html" "</a>")
+ , ("Try this query: http://google.com?search=fish&time=hour.",
+ "Try this query: " <> autolink "http://google.com?search=fish&time=hour" <> ".")
+ , ("HTTPS://GOOGLE.COM,",
+ autolink "HTTPS://GOOGLE.COM" <> ",")
+ , ("http://el.wikipedia.org/wiki/Τεχνολογία,",
+ autolink "http://el.wikipedia.org/wiki/Τεχνολογία" <> ",")
+ , ("doi:10.1000/182,",
+ autolink "doi:10.1000/182" <> ",")
+ , ("git://github.com/foo/bar.git,",
+ autolink "git://github.com/foo/bar.git" <> ",")
+ , ("file:///Users/joe/joe.txt, and",
+ autolink "file:///Users/joe/joe.txt" <> ", and")
+ , ("mailto:someone@somedomain.com.",
+ autolink "mailto:someone@somedomain.com" <> ".")
+ , ("Use http: this is not a link!",
+ "Use http: this is not a link!")
+ , ("(http://google.com).",
+ "(" <> autolink "http://google.com" <> ").")
+ , ("http://en.wikipedia.org/wiki/Sprite_(computer_graphics)",
+ autolink "http://en.wikipedia.org/wiki/Sprite_(computer_graphics)")
+ , ("http://en.wikipedia.org/wiki/Sprite_[computer_graphics]",
+ link "http://en.wikipedia.org/wiki/Sprite_%5Bcomputer_graphics%5D" ""
+ (str "http://en.wikipedia.org/wiki/Sprite_[computer_graphics]"))
+ , ("http://en.wikipedia.org/wiki/Sprite_{computer_graphics}",
+ link "http://en.wikipedia.org/wiki/Sprite_%7Bcomputer_graphics%7D" ""
+ (str "http://en.wikipedia.org/wiki/Sprite_{computer_graphics}"))
+ , ("http://example.com/Notification_Center-GitHub-20101108-140050.jpg",
+ autolink "http://example.com/Notification_Center-GitHub-20101108-140050.jpg")
+ , ("https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20",
+ autolink "https://github.com/github/hubot/blob/master/scripts/cream.js#L20-20")
+ , ("http://www.rubyonrails.com",
+ autolink "http://www.rubyonrails.com")
+ , ("http://www.rubyonrails.com:80",
+ autolink "http://www.rubyonrails.com:80")
+ , ("http://www.rubyonrails.com/~minam",
+ autolink "http://www.rubyonrails.com/~minam")
+ , ("https://www.rubyonrails.com/~minam",
+ autolink "https://www.rubyonrails.com/~minam")
+ , ("http://www.rubyonrails.com/~minam/url%20with%20spaces",
+ autolink "http://www.rubyonrails.com/~minam/url%20with%20spaces")
+ , ("http://www.rubyonrails.com/foo.cgi?something=here",
+ autolink "http://www.rubyonrails.com/foo.cgi?something=here")
+ , ("http://www.rubyonrails.com/foo.cgi?something=here&and=here",
+ autolink "http://www.rubyonrails.com/foo.cgi?something=here&and=here")
+ , ("http://www.rubyonrails.com/contact;new",
+ autolink "http://www.rubyonrails.com/contact;new")
+ , ("http://www.rubyonrails.com/contact;new%20with%20spaces",
+ autolink "http://www.rubyonrails.com/contact;new%20with%20spaces")
+ , ("http://www.rubyonrails.com/contact;new?with=query&string=params",
+ autolink "http://www.rubyonrails.com/contact;new?with=query&string=params")
+ , ("http://www.rubyonrails.com/~minam/contact;new?with=query&string=params",
+ autolink "http://www.rubyonrails.com/~minam/contact;new?with=query&string=params")
+ , ("http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007",
+ autolink "http://en.wikipedia.org/wiki/Wikipedia:Today%27s_featured_picture_%28animation%29/January_20%2C_2007")
+ , ("http://www.mail-archive.com/rails@lists.rubyonrails.org/",
+ autolink "http://www.mail-archive.com/rails@lists.rubyonrails.org/")
+ , ("http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1",
+ autolink "http://www.amazon.com/Testing-Equal-Sign-In-Path/ref=pd_bbs_sr_1?ie=UTF8&s=books&qid=1198861734&sr=8-1")
+ , ("http://en.wikipedia.org/wiki/Texas_hold%27em",
+ autolink "http://en.wikipedia.org/wiki/Texas_hold%27em")
+ , ("https://www.google.com/doku.php?id=gps:resource:scs:start",
+ autolink "https://www.google.com/doku.php?id=gps:resource:scs:start")
+ , ("http://www.rubyonrails.com",
+ autolink "http://www.rubyonrails.com")
+ , ("http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281",
+ autolink "http://manuals.ruby-on-rails.com/read/chapter.need_a-period/103#page281")
+ , ("http://foo.example.com/controller/action?parm=value&p2=v2#anchor123",
+ autolink "http://foo.example.com/controller/action?parm=value&p2=v2#anchor123")
+ , ("http://foo.example.com:3000/controller/action",
+ autolink "http://foo.example.com:3000/controller/action")
+ , ("http://foo.example.com:3000/controller/action+pack",
+ autolink "http://foo.example.com:3000/controller/action+pack")
+ , ("http://business.timesonline.co.uk/article/0,,9065-2473189,00.html",
+ autolink "http://business.timesonline.co.uk/article/0,,9065-2473189,00.html")
+ , ("http://www.mail-archive.com/ruby-talk@ruby-lang.org/",
+ autolink "http://www.mail-archive.com/ruby-talk@ruby-lang.org/")
+ , ("https://example.org/?anchor=lala-",
+ autolink "https://example.org/?anchor=lala-")
+ , ("https://example.org/?anchor=-lala",
+ autolink "https://example.org/?anchor=-lala")
+ ]
+
+{-
+p_markdown_round_trip :: Block -> Bool
+p_markdown_round_trip b = matches d' d''
+ where d' = normalize $ Pandoc (Meta [] [] []) [b]
+ d'' = normalize
+ $ readMarkdown def { readerSmart = True }
+ $ writeMarkdown def d'
+ matches (Pandoc _ [Plain []]) (Pandoc _ []) = True
+ matches (Pandoc _ [Para []]) (Pandoc _ []) = True
+ matches (Pandoc _ [Plain xs]) (Pandoc _ [Para xs']) = xs == xs'
+ matches x y = x == y
+-}
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ "with attribute" =:
+ "`document.write(\"Hello\");`{.javascript}"
+ =?> para
+ (codeWith ("",["javascript"],[]) "document.write(\"Hello\");")
+ , "with attribute space" =:
+ "`*` {.haskell .special x=\"7\"}"
+ =?> para (code "*" <> space <> str "{.haskell" <> space <>
+ str ".special" <> space <> str "x=\"7\"}")
+ ]
+ , testGroup "emph and strong"
+ [ "two strongs in emph" =:
+ "***a**b **c**d*" =?> para (emph (strong (str "a") <> str "b" <> space
+ <> strong (str "c") <> str "d"))
+ , "emph and strong emph alternating" =:
+ "*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx"
+ =?> para (emph "xxx" <> space <> strong (emph "xxx") <>
+ space <> "xxx" <> softbreak <>
+ emph "xxx" <> space <> strong (emph "xxx") <>
+ space <> "xxx")
+ , "emph with spaced strong" =:
+ "*x **xx** x*"
+ =?> para (emph ("x" <> space <> strong "xx" <> space <> "x"))
+ , "intraword underscore with opening underscore (#1121)" =:
+ "_foot_ball_" =?> para (emph (text "foot_ball"))
+ ]
+ , testGroup "raw LaTeX"
+ [ "in URL" =:
+ "\\begin\n" =?> para (text "\\begin")
+ ]
+ , testGroup "raw HTML"
+ [ "nesting (issue #1330)" =:
+ "<del>test</del>" =?>
+ rawBlock "html" "<del>" <> plain (str "test") <>
+ rawBlock "html" "</del>"
+ , "invalid tag (issue #1820" =:
+ "</ div></.div>" =?>
+ para (text "</ div></.div>")
+ , "technically invalid comment" =:
+ "<!-- pandoc --help -->" =?>
+ rawBlock "html" "<!-- pandoc --help -->"
+ , test markdownGH "issue 2469" $
+ "<\n\na>" =?>
+ para (text "<") <> para (text "a>")
+ ]
+ , testGroup "raw email addresses"
+ [ test markdownGH "issue 2940" $
+ "**@user**" =?>
+ para (strong (text "@user"))
+ ]
+ , testGroup "emoji"
+ [ test markdownGH "emoji symbols" $
+ ":smile: and :+1:" =?> para (text "😄 and 👍")
+ ]
+ , "unbalanced brackets" =:
+ "[[[[[[[[[[[[hi" =?> para (text "[[[[[[[[[[[[hi")
+ , testGroup "backslash escapes"
+ [ "in URL" =:
+ "[hi](/there\\))"
+ =?> para (link "/there)" "" "hi")
+ , "in title" =:
+ "[hi](/there \"a\\\"a\")"
+ =?> para (link "/there" "a\"a" "hi")
+ , "in reference link title" =:
+ "[hi]\n\n[hi]: /there (a\\)a)"
+ =?> para (link "/there" "a)a" "hi")
+ , "in reference link URL" =:
+ "[hi]\n\n[hi]: /there\\.0"
+ =?> para (link "/there.0" "" "hi")
+ ]
+ , testGroup "bare URIs"
+ (map testBareLink bareLinkTests)
+ , testGroup "autolinks"
+ [ "with unicode dash following" =:
+ "<http://foo.bar>\8212" =?> para (autolink "http://foo.bar" <>
+ str "\8212")
+ , "a partial URL (#2277)" =:
+ "<www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>" =?>
+ para (text "<www.boe.es/buscar/act.php?id=BOE-A-1996-8930#a66>")
+ , "with some attributes" =:
+ "<http://foo.bar>{#i .j .z k=v}" =?>
+ para (autolinkWith ("i", ["j", "z"], [("k", "v")]) "http://foo.bar")
+ , "with some attributes and spaces" =:
+ "<http://foo.bar> {#i .j .z k=v}" =?>
+ para (autolink "http://foo.bar" <> space <> text "{#i .j .z k=v}")
+ ]
+ , testGroup "links"
+ [ "no autolink inside link" =:
+ "[<https://example.org>](url)" =?>
+ para (link "url" "" (text "<https://example.org>"))
+ , "no inline link inside link" =:
+ "[[a](url2)](url)" =?>
+ para (link "url" "" (text "[a](url2)"))
+ , "no bare URI inside link" =:
+ "[https://example.org(](url)" =?>
+ para (link "url" "" (text "https://example.org("))
+ ]
+ , testGroup "Headers"
+ [ "blank line before header" =:
+ "\n# Header\n"
+ =?> headerWith ("header",[],[]) 1 "Header"
+ , "bracketed text (#2062)" =:
+ "# [hi]\n"
+ =?> headerWith ("hi",[],[]) 1 "[hi]"
+ , "ATX header without trailing #s" =:
+ "# Foo bar\n\n" =?>
+ headerWith ("foo-bar",[],[]) 1 "Foo bar"
+ , "ATX header without trailing #s" =:
+ "# Foo bar with # #" =?>
+ headerWith ("foo-bar-with",[],[]) 1 "Foo bar with #"
+ , "setext header" =:
+ "Foo bar\n=\n\n Foo bar 2 \n=" =?>
+ headerWith ("foo-bar",[],[]) 1 "Foo bar"
+ <> headerWith ("foo-bar-2",[],[]) 1 "Foo bar 2"
+ ]
+ , testGroup "Implicit header references"
+ [ "ATX header without trailing #s" =:
+ "# Header\n[header]\n\n[header ]\n\n[ header]" =?>
+ headerWith ("header",[],[]) 1 "Header"
+ <> para (link "#header" "" (text "header"))
+ <> para (link "#header" "" (text "header"))
+ <> para (link "#header" "" (text "header"))
+ , "ATX header with trailing #s" =:
+ "# Foo bar #\n[foo bar]\n\n[foo bar ]\n\n[ foo bar]" =?>
+ headerWith ("foo-bar",[],[]) 1 "Foo bar"
+ <> para (link "#foo-bar" "" (text "foo bar"))
+ <> para (link "#foo-bar" "" (text "foo bar"))
+ <> para (link "#foo-bar" "" (text "foo bar"))
+ , "setext header" =:
+ " Header \n=\n\n[header]\n\n[header ]\n\n[ header]" =?>
+ headerWith ("header",[],[]) 1 "Header"
+ <> para (link "#header" "" (text "header"))
+ <> para (link "#header" "" (text "header"))
+ <> para (link "#header" "" (text "header"))
+ ]
+ , testGroup "smart punctuation"
+ [ test markdownSmart "quote before ellipses"
+ ("'...hi'"
+ =?> para (singleQuoted "…hi"))
+ , test markdownSmart "apostrophe before emph"
+ ("D'oh! A l'*aide*!"
+ =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
+ , test markdownSmart "apostrophe in French"
+ ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
+ =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+ , test markdownSmart "apostrophe after math" $ -- issue #1909
+ "The value of the $x$'s and the systems' condition." =?>
+ para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
+ ]
+ , testGroup "footnotes"
+ [ "indent followed by newline and flush-left text" =:
+ "[^1]\n\n[^1]: my note\n\n \nnot in note\n"
+ =?> para (note (para "my note")) <> para "not in note"
+ , "indent followed by newline and indented text" =:
+ "[^1]\n\n[^1]: my note\n \n in note\n"
+ =?> para (note (para "my note" <> para "in note"))
+ , "recursive note" =:
+ "[^1]\n\n[^1]: See [^1]\n"
+ =?> para (note (para "See [^1]"))
+ ]
+ , testGroup "lhs"
+ [ test (purely $ readMarkdown def{ readerExtensions = enableExtension
+ Ext_literate_haskell pandocExtensions })
+ "inverse bird tracks and html" $
+ "> a\n\n< b\n\n<div>\n"
+ =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a"
+ <>
+ codeBlockWith ("",["sourceCode","haskell"],[]) "b"
+ <>
+ rawBlock "html" "<div>\n\n"
+ ]
+-- the round-trip properties frequently fail
+-- , testGroup "round trip"
+-- [ property "p_markdown_round_trip" p_markdown_round_trip
+-- ]
+ , testGroup "definition lists"
+ [ "no blank space" =:
+ "foo1\n : bar\n\nfoo2\n : bar2\n : bar3\n" =?>
+ definitionList [ (text "foo1", [plain (text "bar")])
+ , (text "foo2", [plain (text "bar2"),
+ plain (text "bar3")])
+ ]
+ , "blank space before first def" =:
+ "foo1\n\n : bar\n\nfoo2\n\n : bar2\n : bar3\n" =?>
+ definitionList [ (text "foo1", [para (text "bar")])
+ , (text "foo2", [para (text "bar2"),
+ plain (text "bar3")])
+ ]
+ , "blank space before second def" =:
+ "foo1\n : bar\n\nfoo2\n : bar2\n\n : bar3\n" =?>
+ definitionList [ (text "foo1", [plain (text "bar")])
+ , (text "foo2", [plain (text "bar2"),
+ para (text "bar3")])
+ ]
+ , "laziness" =:
+ "foo1\n : bar\nbaz\n : bar2\n" =?>
+ definitionList [ (text "foo1", [plain (text "bar" <>
+ softbreak <> text "baz"),
+ plain (text "bar2")])
+ ]
+ , "no blank space before first of two paragraphs" =:
+ "foo1\n : bar\n\n baz\n" =?>
+ definitionList [ (text "foo1", [para (text "bar") <>
+ para (text "baz")])
+ ]
+ , "first line not indented" =:
+ "foo\n: bar\n" =?>
+ definitionList [ (text "foo", [plain (text "bar")]) ]
+ , "list in definition" =:
+ "foo\n: - bar\n" =?>
+ definitionList [ (text "foo", [bulletList [plain (text "bar")]]) ]
+ , "in div" =:
+ "<div>foo\n: - bar\n</div>" =?>
+ divWith nullAttr (definitionList
+ [ (text "foo", [bulletList [plain (text "bar")]]) ])
+ ]
+ , testGroup "+compact_definition_lists"
+ [ test markdownCDL "basic compact list" $
+ "foo1\n: bar\n baz\nfoo2\n: bar2\n" =?>
+ definitionList [ (text "foo1", [plain (text "bar" <> softbreak <>
+ text "baz")])
+ , (text "foo2", [plain (text "bar2")])
+ ]
+ ]
+ , testGroup "lists"
+ [ "issue #1154" =:
+ " - <div>\n first div breaks\n </div>\n\n <button>if this button exists</button>\n\n <div>\n with this div too.\n </div>\n"
+ =?> bulletList [divWith nullAttr (para $ text "first div breaks") <>
+ rawBlock "html" "<button>" <>
+ plain (text "if this button exists") <>
+ rawBlock "html" "</button>" <>
+ divWith nullAttr (para $ text "with this div too.")]
+ , test markdownGH "issue #1636" $
+ T.unlines [ "* a"
+ , "* b"
+ , "* c"
+ , " * d" ]
+ =?>
+ bulletList [ plain "a"
+ , plain "b"
+ , plain "c" <> bulletList [plain "d"] ]
+ ]
+ , testGroup "entities"
+ [ "character references" =:
+ "&lang; &ouml;" =?> para (text "\10216 ö")
+ , "numeric" =:
+ "&#44;&#x44;&#X44;" =?> para (text ",DD")
+ , "in link title" =:
+ "[link](/url \"title &lang; &ouml; &#44;\")" =?>
+ para (link "/url" "title \10216 ö ," (text "link"))
+ ]
+ , testGroup "citations"
+ [ "simple" =:
+ "@item1" =?> para (cite [
+ Citation{ citationId = "item1"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ ] "@item1")
+ , "key starts with digit" =:
+ "@1657:huyghens" =?> para (cite [
+ Citation{ citationId = "1657:huyghens"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ ] "@1657:huyghens")
+ ]
+ , let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita")
+ in testGroup "footnote/link following citation" -- issue #2083
+ [ "footnote" =:
+ T.unlines [ "@cita[^note]"
+ , ""
+ , "[^note]: note" ] =?>
+ para (
+ citation <> note (para $ str "note")
+ )
+ , "normal link" =:
+ "@cita [link](http://www.com)" =?>
+ para (
+ citation <> space <> link "http://www.com" "" (str "link")
+ )
+ , "reference link" =:
+ T.unlines [ "@cita [link][link]"
+ , ""
+ , "[link]: http://www.com" ] =?>
+ para (
+ citation <> space <> link "http://www.com" "" (str "link")
+ )
+ , "short reference link" =:
+ T.unlines [ "@cita [link]"
+ , ""
+ , "[link]: http://www.com" ] =?>
+ para (
+ citation <> space <> link "http://www.com" "" (str "link")
+ )
+ , "implicit header link" =:
+ T.unlines [ "# Header"
+ , "@cita [Header]" ] =?>
+ headerWith ("header",[],[]) 1 (str "Header") <> para (
+ citation <> space <> link "#header" "" (str "Header")
+ )
+ , "regular citation" =:
+ "@cita [foo]" =?>
+ para (
+ cite [Citation "cita" [] [Str "foo"] AuthorInText 0 0]
+ (str "@cita" <> space <> str "[foo]")
+ )
+ ]
+ ]
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
new file mode 100644
index 000000000..508d79e18
--- /dev/null
+++ b/test/Tests/Readers/Muse.hs
@@ -0,0 +1,1224 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Muse (tests) where
+
+import Data.List (intersperse)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Test.Tasty
+import Test.Tasty.QuickCheck
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+import Text.Pandoc.Shared (underlineSpan)
+import Text.Pandoc.Walk (walk)
+
+amuse :: Text -> Pandoc
+amuse = purely $ readMuse def { readerExtensions = extensionsFromList [Ext_amuse]}
+
+emacsMuse :: Text -> Pandoc
+emacsMuse = purely $ readMuse def { readerExtensions = emptyExtensions }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test amuse
+
+spcSep :: [Inlines] -> Inlines
+spcSep = mconcat . intersperse space
+
+-- Tables don't round-trip yet
+--
+makeRoundTrip :: Block -> Block
+makeRoundTrip Table{} = Para [Str "table was here"]
+makeRoundTrip (OrderedList (start, LowerAlpha, _) items) = OrderedList (start, Decimal, Period) items
+makeRoundTrip (OrderedList (start, UpperAlpha, _) items) = OrderedList (start, Decimal, Period) items
+makeRoundTrip x = x
+
+-- Demand that any AST produced by Muse reader and written by Muse writer can be read back exactly the same way.
+-- Currently we remove tables and compare third rewrite to the second.
+-- First and second rewrites are not equal yet.
+roundTrip :: Block -> Bool
+roundTrip b = d'' == d'''
+ where d = walk makeRoundTrip $ Pandoc nullMeta [b]
+ d' = rewrite d
+ d'' = rewrite d'
+ d''' = rewrite d''
+ rewrite = amuse . T.pack . (++ "\n") . T.unpack .
+ purely (writeMuse def { writerExtensions = extensionsFromList [Ext_amuse]
+ , writerWrapText = WrapPreserve
+ })
+
+tests :: [TestTree]
+tests =
+ [ testGroup "Inlines"
+ [ "Plain String" =:
+ "Hello, World" =?>
+ para "Hello, World"
+
+ , "Muse is not XML" =: "&lt;" =?> para "&lt;"
+
+ , "Emphasis" =:
+ "*Foo bar*" =?>
+ para (emph . spcSep $ ["Foo", "bar"])
+
+ , "Comma after closing *" =:
+ "Foo *bar*, baz" =?>
+ para ("Foo " <> emph "bar" <> ", baz")
+
+ , "Letter after closing *" =:
+ "Foo *bar*x baz" =?>
+ para "Foo *bar*x baz"
+
+ , "Letter before opening *" =:
+ "Foo x*bar* baz" =?>
+ para "Foo x*bar* baz"
+
+ , "Emphasis tag" =:
+ "<em>Foo bar</em>" =?>
+ para (emph . spcSep $ ["Foo", "bar"])
+
+ , "Strong" =:
+ "**Cider**" =?>
+ para (strong "Cider")
+
+ , "Strong tag" =: "<strong>Strong</strong>" =?> para (strong "Strong")
+
+ , "Strong Emphasis" =:
+ "***strength***" =?>
+ para (strong . emph $ "strength")
+
+ , test emacsMuse "Underline"
+ ("_Underline_" =?> para (underlineSpan "Underline"))
+
+ , "Superscript tag" =: "<sup>Superscript</sup>" =?> para (superscript "Superscript")
+
+ , "Subscript tag" =: "<sub>Subscript</sub>" =?> para (subscript "Subscript")
+
+ , "Strikeout tag" =: "<del>Strikeout</del>" =?> para (strikeout "Strikeout")
+
+ , "Opening inline tags" =: "foo <em> bar <strong>baz" =?> para "foo <em> bar <strong>baz"
+
+ , "Closing inline tags" =: "foo </em> bar </strong>baz" =?> para "foo </em> bar </strong>baz"
+
+ , "Tag soup" =: "foo <em> bar </strong>baz" =?> para "foo <em> bar </strong>baz"
+
+ -- Both inline tags must be within the same paragraph
+ , "No multiparagraph inline tags" =:
+ T.unlines [ "First line"
+ , "<em>Second line"
+ , ""
+ , "Fourth line</em>"
+ ] =?>
+ para "First line\n<em>Second line" <>
+ para "Fourth line</em>"
+
+ , "Linebreak" =: "Line <br> break" =?> para ("Line" <> linebreak <> "break")
+
+ , "Trailing whitespace inside paragraph" =:
+ T.unlines [ "First line " -- trailing whitespace here
+ , "second line"
+ ]
+ =?> para "First line\nsecond line"
+
+ , "Non-breaking space" =: "Foo~~bar" =?> para "Foo\160bar"
+ , "Single ~" =: "Foo~bar" =?> para "Foo~bar"
+
+ , testGroup "Code markup"
+ [ "Code" =: "=foo(bar)=" =?> para (code "foo(bar)")
+
+ , "Not code" =: "a=b= =c=d" =?> para (text "a=b= =c=d")
+
+ -- Emacs Muse 3.20 parses this as code, we follow Amusewiki
+ , "Not code if closing = is detached" =: "=this is not a code =" =?> para "=this is not a code ="
+
+ , "Not code if opening = is detached" =: "= this is not a code=" =?> para "= this is not a code="
+
+ , "Code if followed by comma" =:
+ "Foo =bar=, baz" =?>
+ para (text "Foo " <> code "bar" <> text ", baz")
+
+ , "One character code" =: "=c=" =?> para (code "c")
+
+ , "Three = characters is not a code" =: "===" =?> para "==="
+
+ , "Multiline code markup" =:
+ "foo =bar\nbaz= end of code" =?>
+ para (text "foo " <> code "bar\nbaz" <> text " end of code")
+
+{- Emacs Muse 3.20 has a bug: it publishes
+ - <p>foo <code>bar
+ -
+ - baz</code> foo</p>
+ - which is displayed as one paragraph by browsers.
+ - We follow Amusewiki here and avoid joining paragraphs.
+ -}
+ , "No multiparagraph code" =:
+ T.unlines [ "foo =bar"
+ , ""
+ , "baz= foo"
+ ] =?>
+ para "foo =bar" <>
+ para "baz= foo"
+
+ , "Code at the beginning of paragraph but not first column" =:
+ " - =foo=" =?> bulletList [ para $ code "foo" ]
+ ]
+
+ , "Code tag" =: "<code>foo(bar)</code>" =?> para (code "foo(bar)")
+
+ , "Verbatim tag" =: "*<verbatim>*</verbatim>*" =?> para (emph "*")
+
+ , "Verbatim inside code" =: "<code><verbatim>foo</verbatim></code>" =?> para (code "<verbatim>foo</verbatim>")
+
+ , "Verbatim tag after text" =: "Foo <verbatim>bar</verbatim>" =?> para "Foo bar"
+
+ -- <em> tag should match with the last </em> tag, not verbatim one
+ , "Nested \"</em>\" inside em tag" =: "<em>foo<verbatim></em></verbatim>bar</em>" =?> para (emph ("foo</em>bar"))
+
+ , testGroup "Links"
+ [ "Link without description" =:
+ "[[https://amusewiki.org/]]" =?>
+ para (link "https://amusewiki.org/" "" (str "https://amusewiki.org/"))
+ , "Link with description" =:
+ "[[https://amusewiki.org/][A Muse Wiki]]" =?>
+ para (link "https://amusewiki.org/" "" (text "A Muse Wiki"))
+ , "Image" =:
+ "[[image.jpg]]" =?>
+ para (image "image.jpg" "" mempty)
+ , "Image with description" =:
+ "[[image.jpg][Image]]" =?>
+ para (image "image.jpg" "" (text "Image"))
+ , "Image link" =:
+ "[[URL:image.jpg]]" =?>
+ para (link "image.jpg" "" (str "image.jpg"))
+ , "Image link with description" =:
+ "[[URL:image.jpg][Image]]" =?>
+ para (link "image.jpg" "" (text "Image"))
+ -- Implicit links are supported in Emacs Muse, but not in Amusewiki:
+ -- https://github.com/melmothx/text-amuse/issues/18
+ --
+ -- This test also makes sure '=' without whitespace is not treated as code markup
+ , "No implicit links" =: "http://example.org/index.php?action=view&id=1"
+ =?> para "http://example.org/index.php?action=view&id=1"
+ ]
+
+ , testGroup "Literal"
+ [ test emacsMuse "Inline literal"
+ ("Foo<literal style=\"html\">lit</literal>bar" =?>
+ para (text "Foo" <> rawInline "html" "lit" <> text "bar"))
+ ]
+ ]
+
+ , testGroup "Blocks"
+ [ testProperty "Round trip" roundTrip,
+ "Block elements end paragraphs" =:
+ T.unlines [ "First paragraph"
+ , "----"
+ , "Second paragraph"
+ ] =?> para (text "First paragraph") <> horizontalRule <> para (text "Second paragraph")
+ , testGroup "Horizontal rule"
+ [ "Less than 4 dashes is not a horizontal rule" =: "---" =?> para (text "---")
+ , "4 dashes is a horizontal rule" =: "----" =?> horizontalRule
+ , "5 dashes is a horizontal rule" =: "-----" =?> horizontalRule
+ , "4 dashes with spaces is a horizontal rule" =: "---- " =?> horizontalRule
+ ]
+ , testGroup "Paragraphs"
+ [ "Simple paragraph" =:
+ T.unlines [ "First line"
+ , "second line."
+ ] =?>
+ para "First line\nsecond line."
+ , "Indented paragraph" =:
+ T.unlines [ " First line"
+ , "second line."
+ ] =?>
+ para "First line\nsecond line."
+ -- Emacs Muse starts a blockquote on the second line.
+ -- We copy Amusewiki behavior and require a blank line to start a blockquote.
+ , "Indentation in the middle of paragraph" =:
+ T.unlines [ "First line"
+ , " second line"
+ , "third line"
+ ] =?>
+ para "First line\nsecond line\nthird line"
+ , "Quote" =:
+ " This is a quotation\n" =?>
+ blockQuote (para "This is a quotation")
+ , "Indentation does not indicate quote inside quote tag" =:
+ T.unlines [ "<quote>"
+ , " Not a nested quote"
+ , "</quote>"
+ ] =?>
+ blockQuote (para "Not a nested quote")
+ , "Multiline quote" =:
+ T.unlines [ " This is a quotation"
+ , " with a continuation"
+ ] =?>
+ blockQuote (para "This is a quotation\nwith a continuation")
+ , testGroup "Div"
+ [ "Div without id" =:
+ T.unlines [ "<div>"
+ , "Foo bar"
+ , "</div>"
+ ] =?>
+ divWith nullAttr (para "Foo bar")
+ , "Div with id" =:
+ T.unlines [ "<div id=\"foo\">"
+ , "Foo bar"
+ , "</div>"
+ ] =?>
+ divWith ("foo", [], []) (para "Foo bar")
+ ]
+ , "Verse" =:
+ T.unlines [ "> This is"
+ , "> First stanza"
+ , ">" -- Emacs produces verbatim ">" here, we follow Amusewiki
+ , "> And this is"
+ , "> Second stanza"
+ , ">"
+ , ""
+ , ">"
+ , ""
+ , "> Another verse"
+ , "> is here"
+ ] =?>
+ lineBlock [ "This is"
+ , "First stanza"
+ , ""
+ , "And this is"
+ , "\160\160Second stanza"
+ , ""
+ ] <>
+ lineBlock [ "" ] <>
+ lineBlock [ "Another verse"
+ , "\160\160\160is here"
+ ]
+ ]
+ , "Verse in list" =: " - > foo" =?> bulletList [ lineBlock [ "foo" ] ]
+ , "Multiline verse in list" =:
+ T.unlines [ " - > foo"
+ , " > bar"
+ ] =?>
+ bulletList [ lineBlock [ "foo", "bar" ] ]
+ , "Paragraph after verse in list" =:
+ T.unlines [ " - > foo"
+ , " bar"
+ ] =?>
+ bulletList [ lineBlock [ "foo" ] <> para "bar" ]
+ , "Empty quote tag" =:
+ T.unlines [ "<quote>"
+ , "</quote>"
+ ]
+ =?> blockQuote mempty
+ , "Quote tag" =:
+ T.unlines [ "<quote>"
+ , "Hello, world"
+ , "</quote>"
+ ]
+ =?> blockQuote (para $ text "Hello, world")
+ , "Nested quote tag" =:
+ T.unlines [ "<quote>"
+ , "foo"
+ , "<quote>"
+ , "bar"
+ , "</quote>"
+ , "baz"
+ , "</quote>"
+ ] =?>
+ blockQuote (para "foo" <> blockQuote (para "bar") <> para "baz")
+ , "Indented quote inside list" =:
+ T.unlines [ " - <quote>"
+ , " foo"
+ , " </quote>"
+ ] =?>
+ bulletList [ blockQuote (para "foo") ]
+ , "Verse tag" =:
+ T.unlines [ "<verse>"
+ , ""
+ , "Foo bar baz"
+ , " One two three"
+ , ""
+ , "</verse>"
+ ] =?>
+ lineBlock [ ""
+ , text "Foo bar baz"
+ , text "\160\160One two three"
+ , ""
+ ]
+ , "Verse tag with empty line inside" =:
+ T.unlines [ "<verse>"
+ , ""
+ , "</verse>"
+ ] =?>
+ lineBlock [ "" ]
+ , testGroup "Example"
+ [ "Braces on separate lines" =:
+ T.unlines [ "{{{"
+ , "Example line"
+ , "}}}"
+ ] =?>
+ codeBlock "Example line"
+ , "Spaces after opening braces" =:
+ T.unlines [ "{{{ "
+ , "Example line"
+ , "}}}"
+ ] =?>
+ codeBlock "Example line"
+ , "One blank line in the beginning" =:
+ T.unlines [ "{{{"
+ , ""
+ , "Example line"
+ , "}}}"
+ ] =?>
+ codeBlock "\nExample line"
+ , "One blank line in the end" =:
+ T.unlines [ "{{{"
+ , "Example line"
+ , ""
+ , "}}}"
+ ] =?>
+ codeBlock "Example line\n"
+ -- Amusewiki requires braces to be on separate line,
+ -- this is an extension.
+ , "One line" =:
+ "{{{Example line}}}" =?>
+ codeBlock "Example line"
+ ]
+ , testGroup "Example tag"
+ [ "Tags on separate lines" =:
+ T.unlines [ "<example>"
+ , "Example line"
+ , "</example>"
+ ] =?>
+ codeBlock "Example line"
+ , "One line" =:
+ "<example>Example line</example>" =?>
+ codeBlock "Example line"
+ , "One blank line in the beginning" =:
+ T.unlines [ "<example>"
+ , ""
+ , "Example line"
+ , "</example>"
+ ] =?>
+ codeBlock "\nExample line"
+ , "One blank line in the end" =:
+ T.unlines [ "<example>"
+ , "Example line"
+ , ""
+ , "</example>"
+ ] =?>
+ codeBlock "Example line\n"
+ , "Example inside list" =:
+ T.unlines [ " - <example>"
+ , " foo"
+ , " </example>"
+ ] =?>
+ bulletList [ codeBlock "foo" ]
+ , "Empty example inside list" =:
+ T.unlines [ " - <example>"
+ , " </example>"
+ ] =?>
+ bulletList [ codeBlock "" ]
+ , "Example inside list with empty lines" =:
+ T.unlines [ " - <example>"
+ , " foo"
+ , " </example>"
+ , ""
+ , " bar"
+ , ""
+ , " <example>"
+ , " baz"
+ , " </example>"
+ ] =?>
+ bulletList [ codeBlock "foo" <> para "bar" <> codeBlock "baz" ]
+ , "Indented example inside list" =:
+ T.unlines [ " - <example>"
+ , " foo"
+ , " </example>"
+ ] =?>
+ bulletList [ codeBlock "foo" ]
+ , "Example inside definition list" =:
+ T.unlines [ " foo :: <example>"
+ , " bar"
+ , " </example>"
+ ] =?>
+ definitionList [ ("foo", [codeBlock "bar"]) ]
+ , "Example inside list definition with empty lines" =:
+ T.unlines [ " term :: <example>"
+ , " foo"
+ , " </example>"
+ , ""
+ , " bar"
+ , ""
+ , " <example>"
+ , " baz"
+ , " </example>"
+ ] =?>
+ definitionList [ ("term", [codeBlock "foo" <> para "bar" <> codeBlock "baz"]) ]
+ , "Example inside note" =:
+ T.unlines [ "Foo[1]"
+ , ""
+ , "[1] <example>"
+ , " bar"
+ , " </example>"
+ ] =?>
+ para ("Foo" <> note (codeBlock "bar"))
+ ]
+ , testGroup "Literal blocks"
+ [ test emacsMuse "Literal block"
+ (T.unlines [ "<literal style=\"latex\">"
+ , "\\newpage"
+ , "</literal>"
+ ] =?>
+ rawBlock "latex" "\\newpage")
+ ]
+ , "Center" =:
+ T.unlines [ "<center>"
+ , "Hello, world"
+ , "</center>"
+ ] =?>
+ para (text "Hello, world")
+ , "Right" =:
+ T.unlines [ "<right>"
+ , "Hello, world"
+ , "</right>"
+ ] =?>
+ para (text "Hello, world")
+ , testGroup "Comments"
+ [ "Comment tag" =: "<comment>\nThis is a comment\n</comment>" =?> (mempty::Blocks)
+ , "Line comment" =: "; Comment" =?> (mempty::Blocks)
+ , "Empty comment" =: ";" =?> (mempty::Blocks)
+ , "Text after empty comment" =: ";\nfoo" =?> para "foo" -- Make sure we don't consume newline while looking for whitespace
+ , "Not a comment (does not start with a semicolon)" =: " ; Not a comment" =?> para (text "; Not a comment")
+ , "Not a comment (has no space after semicolon)" =: ";Not a comment" =?> para (text ";Not a comment")
+ ]
+ , testGroup "Headers"
+ [ "Part" =:
+ "* First level" =?>
+ header 1 "First level"
+ , "Chapter" =:
+ "** Second level" =?>
+ header 2 "Second level"
+ , "Section" =:
+ "*** Third level" =?>
+ header 3 "Third level"
+ , "Subsection" =:
+ "**** Fourth level" =?>
+ header 4 "Fourth level"
+ , "Subsubsection" =:
+ "***** Fifth level" =?>
+ header 5 "Fifth level"
+ , "Whitespace is required after *" =: "**Not a header" =?> para "**Not a header"
+ , "No headers in footnotes" =:
+ T.unlines [ "Foo[1]"
+ , "[1] * Bar"
+ ] =?>
+ para (text "Foo" <>
+ note (para "* Bar"))
+ , "No headers in quotes" =:
+ T.unlines [ "<quote>"
+ , "* Hi"
+ , "</quote>"
+ ] =?>
+ blockQuote (para "* Hi")
+ , "Headers consume anchors" =:
+ T.unlines [ "** Foo"
+ , "#bar"
+ ] =?>
+ headerWith ("bar",[],[]) 2 "Foo"
+ , "Headers don't consume anchors separated with a blankline" =:
+ T.unlines [ "** Foo"
+ , ""
+ , "#bar"
+ ] =?>
+ header 2 "Foo" <>
+ para (spanWith ("bar", [], []) mempty)
+ , "Headers terminate lists" =:
+ T.unlines [ " - foo"
+ , "* bar"
+ ] =?>
+ bulletList [ para "foo" ] <>
+ header 1 "bar"
+ ]
+ , testGroup "Directives"
+ [ "Title" =:
+ "#title Document title" =?>
+ let titleInline = toList "Document title"
+ meta = setMeta "title" (MetaInlines titleInline) nullMeta
+ in Pandoc meta mempty
+ -- Emacs Muse documentation says that "You can use any combination
+ -- of uppercase and lowercase letters for directives",
+ -- but also allows '-', which is not documented, but used for disable-tables.
+ , test emacsMuse "Disable tables"
+ ("#disable-tables t" =?>
+ Pandoc (setMeta "disable-tables" (MetaInlines $ toList "t") nullMeta) mempty)
+ , "Multiple directives" =:
+ T.unlines [ "#title Document title"
+ , "#subtitle Document subtitle"
+ ] =?>
+ Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $
+ setMeta "subtitle" (MetaInlines $ toList "Document subtitle") nullMeta) mempty
+ , "Multiline directive" =:
+ T.unlines [ "#title Document title"
+ , "#notes First line"
+ , "and second line"
+ , "#author Name"
+ ] =?>
+ Pandoc (setMeta "title" (MetaInlines $ toList "Document title") $
+ setMeta "notes" (MetaInlines $ toList "First line\nand second line") $
+ setMeta "author" (MetaInlines $ toList "Name") nullMeta) mempty
+ ]
+ , testGroup "Anchors"
+ [ "Anchor" =:
+ T.unlines [ "; A comment to make sure anchor is not parsed as a directive"
+ , "#anchor Target"
+ ] =?>
+ para (spanWith ("anchor", [], []) mempty <> "Target")
+ , "Anchor cannot start with a number" =:
+ T.unlines [ "; A comment to make sure anchor is not parsed as a directive"
+ , "#0notanchor Target"
+ ] =?>
+ para "#0notanchor Target"
+ , "Not anchor if starts with a space" =:
+ " #notanchor Target" =?>
+ para "#notanchor Target"
+ , "Anchor inside a paragraph" =:
+ T.unlines [ "Paragraph starts here"
+ , "#anchor and ends here."
+ ] =?>
+ para ("Paragraph starts here\n" <> spanWith ("anchor", [], []) mempty <> "and ends here.")
+ ]
+ , testGroup "Footnotes"
+ [ "Simple footnote" =:
+ T.unlines [ "Here is a footnote[1]."
+ , ""
+ , "[1] Footnote contents"
+ ] =?>
+ para (text "Here is a footnote" <>
+ note (para "Footnote contents") <>
+ str ".")
+ , "Recursive footnote" =:
+ T.unlines [ "Start recursion here[1]"
+ , ""
+ , "[1] Recursion continues here[1]"
+ ] =?>
+ para (text "Start recursion here" <>
+ note (para "Recursion continues here[1]"))
+ , "No zero footnotes" =:
+ T.unlines [ "Here is a footnote[0]."
+ , ""
+ , "[0] Footnote contents"
+ ] =?>
+ para "Here is a footnote[0]." <>
+ para "[0] Footnote contents"
+ , "Footnotes can't start with zero" =:
+ T.unlines [ "Here is a footnote[01]."
+ , ""
+ , "[01] Footnote contents"
+ ] =?>
+ para "Here is a footnote[01]." <>
+ para "[01] Footnote contents"
+ , testGroup "Multiparagraph footnotes"
+ [ "Amusewiki multiparagraph footnotes" =:
+ T.unlines [ "Multiparagraph[1] footnotes[2]"
+ , ""
+ , "[1] First footnote paragraph"
+ , ""
+ , " Second footnote paragraph"
+ , "with continuation"
+ , ""
+ , "Not a note"
+ , "[2] Second footnote"
+ ] =?>
+ para (text "Multiparagraph" <>
+ note (para "First footnote paragraph" <>
+ para "Second footnote paragraph\nwith continuation") <>
+ text " footnotes" <>
+ note (para "Second footnote")) <>
+ para (text "Not a note")
+
+ -- Verse requires precise indentation, so it is good to test indentation requirements
+ , "Note continuation with verse" =:
+ T.unlines [ "Foo[1]"
+ , ""
+ , "[1] Bar"
+ , ""
+ , " > Baz"
+ ] =?>
+ para ("Foo" <> note (para "Bar" <> lineBlock ["Baz"]))
+ , test emacsMuse "Emacs multiparagraph footnotes"
+ (T.unlines
+ [ "First footnote reference[1] and second footnote reference[2]."
+ , ""
+ , "[1] First footnote paragraph"
+ , ""
+ , "Second footnote"
+ , "paragraph"
+ , ""
+ , "[2] Third footnote paragraph"
+ , ""
+ , "Fourth footnote paragraph"
+ ] =?>
+ para (text "First footnote reference" <>
+ note (para "First footnote paragraph" <>
+ para "Second footnote\nparagraph") <>
+ text " and second footnote reference" <>
+ note (para "Third footnote paragraph" <>
+ para "Fourth footnote paragraph") <>
+ text "."))
+ ]
+ ]
+ ]
+ , testGroup "Tables"
+ [ "Two cell table" =:
+ "One | Two" =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[plain "One", plain "Two"]]
+ , "Table with multiple words" =:
+ "One two | three four" =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[plain "One two", plain "three four"]]
+ , "Not a table" =:
+ "One| Two" =?>
+ para (text "One| Two")
+ , "Not a table again" =:
+ "One |Two" =?>
+ para (text "One |Two")
+ , "Two line table" =:
+ T.unlines
+ [ "One | Two"
+ , "Three | Four"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[plain "One", plain "Two"],
+ [plain "Three", plain "Four"]]
+ , "Table with one header" =:
+ T.unlines
+ [ "First || Second"
+ , "Third | Fourth"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ [plain "First", plain "Second"]
+ [[plain "Third", plain "Fourth"]]
+ , "Table with two headers" =:
+ T.unlines
+ [ "First || header"
+ , "Second || header"
+ , "Foo | bar"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ [plain "First", plain "header"]
+ [[plain "Second", plain "header"],
+ [plain "Foo", plain "bar"]]
+ , "Header and footer reordering" =:
+ T.unlines
+ [ "Foo ||| bar"
+ , "Baz || foo"
+ , "Bar | baz"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ [plain "Baz", plain "foo"]
+ [[plain "Bar", plain "baz"],
+ [plain "Foo", plain "bar"]]
+ , "Table with caption" =:
+ T.unlines
+ [ "Foo || bar || baz"
+ , "First | row | here"
+ , "Second | row | there"
+ , "|+ Table caption +|"
+ ] =?>
+ table (text "Table caption") (replicate 3 (AlignDefault, 0.0))
+ [plain "Foo", plain "bar", plain "baz"]
+ [[plain "First", plain "row", plain "here"],
+ [plain "Second", plain "row", plain "there"]]
+ , "Caption without table" =:
+ "|+ Foo bar baz +|" =?>
+ table (text "Foo bar baz") [] [] []
+ , "Table indented with space" =:
+ T.unlines
+ [ " Foo | bar"
+ , " Baz | foo"
+ , " Bar | baz"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ []
+ [[plain "Foo", plain "bar"],
+ [plain "Baz", plain "foo"],
+ [plain "Bar", plain "baz"]]
+ , "Empty cells" =:
+ T.unlines
+ [ " | Foo"
+ , " |"
+ , " bar |"
+ , " || baz"
+ ] =?>
+ table mempty [(AlignDefault, 0.0), (AlignDefault, 0.0)]
+ [plain "", plain "baz"]
+ [[plain "", plain "Foo"],
+ [plain "", plain ""],
+ [plain "bar", plain ""]]
+ ]
+ , testGroup "Lists"
+ [ "Bullet list" =:
+ T.unlines
+ [ " - Item1"
+ , ""
+ , " - Item2"
+ ] =?>
+ bulletList [ para "Item1"
+ , para "Item2"
+ ]
+ , "Ordered list" =:
+ T.unlines
+ [ " 1. Item1"
+ , ""
+ , " 2. Item2"
+ ] =?>
+ orderedListWith (1, Decimal, Period) [ para "Item1"
+ , para "Item2"
+ ]
+ , "Ordered list with implicit numbers" =:
+ T.unlines
+ [ " 1. Item1"
+ , ""
+ , " 1. Item2"
+ , ""
+ , " 1. Item3"
+ ] =?>
+ orderedListWith (1, Decimal, Period) [ para "Item1"
+ , para "Item2"
+ , para "Item3"
+ ]
+ , "Ordered list with roman numerals" =:
+ T.unlines
+ [ " i. First"
+ , " ii. Second"
+ , " iii. Third"
+ , " iv. Fourth"
+ ] =?>
+ orderedListWith (1, LowerRoman, Period) [ para "First"
+ , para "Second"
+ , para "Third"
+ , para "Fourth"
+ ]
+ , "Bullet list with empty items" =:
+ T.unlines
+ [ " -"
+ , ""
+ , " - Item2"
+ ] =?>
+ bulletList [ mempty
+ , para "Item2"
+ ]
+ , "Ordered list with empty items" =:
+ T.unlines
+ [ " 1."
+ , ""
+ , " 2."
+ , ""
+ , " 3. Item3"
+ ] =?>
+ orderedListWith (1, Decimal, Period) [ mempty
+ , mempty
+ , para "Item3"
+ ]
+ , "Bullet list with last item empty" =:
+ T.unlines
+ [ " -"
+ , ""
+ , "foo"
+ ] =?>
+ bulletList [ mempty ] <>
+ para "foo"
+ , testGroup "Nested lists"
+ [ "Nested bullet list" =:
+ T.unlines [ " - Item1"
+ , " - Item2"
+ , " - Item3"
+ , " - Item4"
+ , " - Item5"
+ , " - Item6"
+ ] =?>
+ bulletList [ para "Item1" <>
+ bulletList [ para "Item2" <>
+ bulletList [ para "Item3" ]
+ , para "Item4" <>
+ bulletList [ para "Item5" ]
+ ]
+ , para "Item6"
+ ]
+ , "Nested ordered list" =:
+ T.unlines [ " 1. Item1"
+ , " 1. Item2"
+ , " 1. Item3"
+ , " 2. Item4"
+ , " 1. Item5"
+ , " 2. Item6"
+ ] =?>
+ orderedListWith (1, Decimal, Period) [ para "Item1" <>
+ orderedListWith (1, Decimal, Period) [ para "Item2" <>
+ orderedListWith (1, Decimal, Period) [ para "Item3" ]
+ , para "Item4" <>
+ orderedListWith (1, Decimal, Period) [ para "Item5" ]
+ ]
+ , para "Item6"
+ ]
+ , "Mixed nested list" =:
+ T.unlines
+ [ " - Item1"
+ , " - Item2"
+ , " - Item3"
+ , " - Item4"
+ , " 1. Nested"
+ , " 2. Ordered"
+ , " 3. List"
+ ] =?>
+ bulletList [ mconcat [ para "Item1"
+ , bulletList [ para "Item2"
+ , para "Item3"
+ ]
+ ]
+ , mconcat [ para "Item4"
+ , orderedListWith (1, Decimal, Period) [ para "Nested"
+ , para "Ordered"
+ , para "List"
+ ]
+ ]
+ ]
+ , "Text::Amuse includes only one space in list marker" =:
+ T.unlines
+ [ " - First item"
+ , " - Nested item"
+ ] =?>
+ bulletList [ para "First item" <> bulletList [ para "Nested item"]]
+ ]
+ , "List continuation" =:
+ T.unlines
+ [ " - a"
+ , ""
+ , " b"
+ , ""
+ , " c"
+ ] =?>
+ bulletList [ mconcat [ para "a"
+ , para "b"
+ , para "c"
+ ]
+ ]
+ , "List continuation afeter nested list" =:
+ T.unlines
+ [ " - - foo"
+ , ""
+ , " bar"
+ ] =?>
+ bulletList [ bulletList [ para "foo" ] <>
+ para "bar"
+ ]
+ -- Emacs Muse allows to separate lists with two or more blank lines.
+ -- Text::Amuse (Amusewiki engine) always creates a single list as of version 0.82.
+ -- pandoc follows Emacs Muse behavior
+ , testGroup "Blank lines"
+ [ "Blank lines between list items are not required" =:
+ T.unlines
+ [ " - Foo"
+ , " - Bar"
+ ] =?>
+ bulletList [ para "Foo"
+ , para "Bar"
+ ]
+ , "One blank line between list items is allowed" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , " - Bar"
+ ] =?>
+ bulletList [ para "Foo"
+ , para "Bar"
+ ]
+ , "Two blank lines separate lists" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , ""
+ , " - Bar"
+ ] =?>
+ bulletList [ para "Foo" ] <> bulletList [ para "Bar" ]
+ , "No blank line after multiline first item" =:
+ T.unlines
+ [ " - Foo"
+ , " bar"
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo\nbar"
+ , para "Baz"
+ ]
+ , "One blank line after multiline first item" =:
+ T.unlines
+ [ " - Foo"
+ , " bar"
+ , ""
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo\nbar"
+ , para "Baz"
+ ]
+ , "Two blank lines after multiline first item" =:
+ T.unlines
+ [ " - Foo"
+ , " bar"
+ , ""
+ , ""
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo\nbar" ] <> bulletList [ para "Baz" ]
+ , "No blank line after list continuation" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , " bar"
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo" <> para "bar"
+ , para "Baz"
+ ]
+ , "One blank line after list continuation" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , " bar"
+ , ""
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo" <> para "bar"
+ , para "Baz"
+ ]
+ , "Two blank lines after list continuation" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , " bar"
+ , ""
+ , ""
+ , " - Baz"
+ ] =?>
+ bulletList [ para "Foo" <> para "bar" ] <> bulletList [ para "Baz" ]
+ , "No blank line after blockquote" =:
+ T.unlines
+ [ " - <quote>"
+ , " foo"
+ , " </quote>"
+ , " - bar"
+ ] =?>
+ bulletList [ blockQuote $ para "foo", para "bar" ]
+ , "One blank line after blockquote" =:
+ T.unlines
+ [ " - <quote>"
+ , " foo"
+ , " </quote>"
+ , ""
+ , " - bar"
+ ] =?>
+ bulletList [ blockQuote $ para "foo", para "bar" ]
+ , "Two blank lines after blockquote" =:
+ T.unlines
+ [ " - <quote>"
+ , " foo"
+ , " </quote>"
+ , ""
+ , ""
+ , " - bar"
+ ] =?>
+ bulletList [ blockQuote $ para "foo" ] <> bulletList [ para "bar" ]
+ , "No blank line after verse" =:
+ T.unlines
+ [ " - > foo"
+ , " - bar"
+ ] =?>
+ bulletList [ lineBlock [ "foo" ], para "bar" ]
+ , "One blank line after verse" =:
+ T.unlines
+ [ " - > foo"
+ , ""
+ , " - bar"
+ ] =?>
+ bulletList [ lineBlock [ "foo" ], para "bar" ]
+ , "Two blank lines after verse" =:
+ T.unlines
+ [ " - > foo"
+ , ""
+ , ""
+ , " - bar"
+ ] =?>
+ bulletList [ lineBlock [ "foo" ] ] <> bulletList [ para "bar" ]
+ ]
+ -- Test that definition list requires a leading space.
+ -- Emacs Muse does not require a space, we follow Amusewiki here.
+ , "Not a definition list" =:
+ T.unlines
+ [ "First :: second"
+ , "Foo :: bar"
+ ] =?>
+ para "First :: second\nFoo :: bar"
+ , test emacsMuse "Emacs Muse definition list"
+ (T.unlines
+ [ "First :: second"
+ , "Foo :: bar"
+ ] =?>
+ definitionList [ ("First", [ para "second" ])
+ , ("Foo", [ para "bar" ])
+ ])
+ , "Definition list" =:
+ T.unlines
+ [ " First :: second"
+ , " Foo :: bar"
+ ] =?>
+ definitionList [ ("First", [ para "second" ])
+ , ("Foo", [ para "bar" ])
+ ]
+ , "Definition list term cannot include newline" =:
+ T.unlines
+ [ " Foo" -- "Foo" is not a part of the definition list term
+ , " Bar :: baz"
+ ] =?>
+ para "Foo" <>
+ definitionList [ ("Bar", [ para "baz" ]) ]
+ , "One-line definition list" =: " foo :: bar" =?>
+ definitionList [ ("foo", [ para "bar" ]) ]
+ , "Definition list term may include single colon" =:
+ " foo:bar :: baz" =?>
+ definitionList [ ("foo:bar", [ para "baz" ]) ]
+ , "Definition list term with emphasis" =: " *Foo* :: bar\n" =?>
+ definitionList [ (emph "Foo", [ para "bar" ]) ]
+ , "Definition list term with :: inside code" =: " foo <code> :: </code> :: bar <code> :: </code> baz\n" =?>
+ definitionList [ ("foo " <> code " :: ", [ para $ "bar " <> code " :: " <> " baz" ]) ]
+ , "Multi-line definition lists" =:
+ T.unlines
+ [ " First term :: Definition of first term"
+ , "and its continuation."
+ , " Second term :: Definition of second term."
+ ] =?>
+ definitionList [ ("First term", [ para "Definition of first term\nand its continuation." ])
+ , ("Second term", [ para "Definition of second term." ])
+ ]
+ , test emacsMuse "Multi-line definition lists from Emacs Muse manual"
+ (T.unlines
+ [ "Term1 ::"
+ , " This is a first definition"
+ , " And it has two lines;"
+ , "no, make that three."
+ , ""
+ , "Term2 :: This is a second definition"
+ ] =?>
+ definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."])
+ , ("Term2", [ para "This is a second definition"])
+ ])
+ -- Text::Amuse requires indentation with one space
+ , "Multi-line definition lists from Emacs Muse manual with initial space" =:
+ (T.unlines
+ [ " Term1 ::"
+ , " This is a first definition"
+ , " And it has two lines;"
+ , "no, make that three."
+ , ""
+ , " Term2 :: This is a second definition"
+ ] =?>
+ definitionList [ ("Term1", [ para "This is a first definition\nAnd it has two lines;\nno, make that three."])
+ , ("Term2", [ para "This is a second definition"])
+ ])
+ , "One-line nested definition list" =:
+ " Foo :: bar :: baz" =?>
+ definitionList [ ("Foo", [ definitionList [ ("bar", [ para "baz" ])]])]
+ , "Nested definition list" =:
+ T.unlines
+ [ " First :: Second :: Third"
+ , " Fourth :: Fifth :: Sixth"
+ , " Seventh :: Eighth"
+ ] =?>
+ definitionList [ ("First", [ definitionList [ ("Second", [ para "Third" ]),
+ ("Fourth", [ definitionList [ ("Fifth", [ para "Sixth"] ) ] ] ) ] ] )
+ , ("Seventh", [ para "Eighth" ])
+ ]
+ , testGroup "Definition lists with multiple descriptions"
+ [ "Correctly indented second description" =:
+ T.unlines
+ [ " First term :: first description"
+ , " :: second description"
+ ] =?>
+ definitionList [ ("First term", [ para "first description"
+ , para "second description"
+ ])
+ ]
+ , "Incorrectly indented second description" =:
+ T.unlines
+ [ " First term :: first description"
+ , " :: second description"
+ ] =?>
+ definitionList [ ("First term", [ para "first description" ])
+ , ("", [ para "second description" ])
+ ]
+ ]
+ , "Two blank lines separate definition lists" =:
+ T.unlines
+ [ " First :: list"
+ , ""
+ , ""
+ , " Second :: list"
+ ] =?>
+ definitionList [ ("First", [ para "list" ]) ] <>
+ definitionList [ ("Second", [ para "list" ]) ]
+ -- Headers in first column of list continuation are not allowed
+ , "No headers in list continuation" =:
+ T.unlines
+ [ " - Foo"
+ , ""
+ , " * Bar"
+ ] =?>
+ bulletList [ mconcat [ para "Foo"
+ , para "* Bar"
+ ]
+ ]
+ , "Bullet list inside a tag" =:
+ T.unlines
+ [ "<quote>"
+ , " - First"
+ , ""
+ , " - Second"
+ , ""
+ , " - Third"
+ , "</quote>"
+ ] =?>
+ blockQuote (bulletList [ para "First"
+ , para "Second"
+ , para "Third"
+ ])
+ , "Ordered list inside a tag" =:
+ T.unlines
+ [ "<quote>"
+ , " 1. First"
+ , ""
+ , " 2. Second"
+ , ""
+ , " 3. Third"
+ , "</quote>"
+ ] =?>
+ blockQuote (orderedListWith (1, Decimal, Period) [ para "First"
+ , para "Second"
+ , para "Third"
+ ])
+ -- Regression test for a bug caught by round-trip test
+ , "Do not consume whitespace while looking for end tag" =:
+ T.unlines
+ [ "<quote>"
+ , " - <quote>"
+ , " foo"
+ , " </quote>"
+ , " bar" -- Do not consume whitespace while looking for arbitraritly indented </quote>
+ , "</quote>"
+ ] =?>
+ blockQuote (bulletList [ blockQuote $ para "foo" ] <> para "bar")
+ ]
+ ]
diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs
new file mode 100644
index 000000000..4b7058cf9
--- /dev/null
+++ b/test/Tests/Readers/Odt.hs
@@ -0,0 +1,170 @@
+module Tests.Readers.Odt (tests) where
+
+import Control.Monad (liftM)
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as B
+import qualified Data.Map as M
+import Data.Text (unpack)
+import System.IO.Unsafe (unsafePerformIO)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import qualified Text.Pandoc.UTF8 as UTF8
+
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "odt" }
+
+tests :: [TestTree]
+tests = testsComparingToMarkdown ++ testsComparingToNative
+
+testsComparingToMarkdown :: [TestTree]
+testsComparingToMarkdown = map nameToTest namesOfTestsComparingToMarkdown
+ where nameToTest name = createTest
+ compareOdtToMarkdown
+ name
+ (toOdtPath name)
+ (toMarkdownPath name)
+ toOdtPath name = "odt/odt/" ++ name ++ ".odt"
+ toMarkdownPath name = "odt/markdown/" ++ name ++ ".md"
+
+testsComparingToNative :: [TestTree]
+testsComparingToNative = map nameToTest namesOfTestsComparingToNative
+ where nameToTest name = createTest
+ compareOdtToNative
+ name
+ (toOdtPath name)
+ (toNativePath name)
+ toOdtPath name = "odt/odt/" ++ name ++ ".odt"
+ toNativePath name = "odt/native/" ++ name ++ ".native"
+
+
+newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
+ deriving ( Show )
+
+instance ToString NoNormPandoc where
+ toString d = unpack $
+ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ where s = case d of
+ NoNormPandoc (Pandoc (Meta m) _)
+ | M.null m -> Nothing
+ | otherwise -> Just "" -- need this for Meta output
+
+instance ToPandoc NoNormPandoc where
+ toPandoc = unNoNorm
+
+getNoNormVia :: (a -> Pandoc) -> String -> Either PandocError a -> NoNormPandoc
+getNoNormVia _ readerName (Left _) = error (readerName ++ " reader failed")
+getNoNormVia f _ (Right a) = NoNormPandoc (f a)
+
+type TestCreator = ReaderOptions
+ -> FilePath -> FilePath
+ -> IO (NoNormPandoc, NoNormPandoc)
+
+compareOdtToNative :: TestCreator
+compareOdtToNative opts odtPath nativePath = do
+ nativeFile <- UTF8.toText <$> BS.readFile nativePath
+ odtFile <- B.readFile odtPath
+ native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile)
+ odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
+ return (odt,native)
+
+compareOdtToMarkdown :: TestCreator
+compareOdtToMarkdown opts odtPath markdownPath = do
+ markdownFile <- UTF8.toText <$> BS.readFile markdownPath
+ odtFile <- B.readFile odtPath
+ markdown <- getNoNormVia id "markdown" <$>
+ runIO (readMarkdown def{ readerExtensions = pandocExtensions }
+ markdownFile)
+ odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
+ return (odt,markdown)
+
+
+createTest :: TestCreator
+ -> TestName
+ -> FilePath -> FilePath
+ -> TestTree
+createTest creator name path1 path2 =
+ unsafePerformIO $ liftM (test id name) (creator defopts path1 path2)
+
+{-
+--
+
+getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
+getMedia archivePath mediaPath = do
+ zf <- B.readFile archivePath >>= return . toArchive
+ return $ findEntryByPath ("Pictures/" ++ mediaPath) zf >>= (Just . fromEntry)
+
+compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
+compareMediaPathIO mediaPath mediaBag odtPath = do
+ odtMedia <- getMedia odtPath mediaPath
+ let mbBS = case lookupMedia mediaPath mediaBag of
+ Just (_, bs) -> bs
+ Nothing -> error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")
+ odtBS = case odtMedia of
+ Just bs -> bs
+ Nothing -> error ("couldn't find " ++
+ mediaPath ++
+ " in media bag")
+ return $ mbBS == odtBS
+
+compareMediaBagIO :: FilePath -> IO Bool
+compareMediaBagIO odtFile = do
+ df <- B.readFile odtFile
+ let (_, mb) = readOdt def df
+ bools <- mapM
+ (\(fp, _, _) -> compareMediaPathIO fp mb odtFile)
+ (mediaDirectory mb)
+ return $ and bools
+
+testMediaBagIO :: String -> FilePath -> IO TestTree
+testMediaBagIO name odtFile = do
+ outcome <- compareMediaBagIO odtFile
+ return $ testCase name (assertBool
+ ("Media didn't match media bag in file " ++ odtFile)
+ outcome)
+
+testMediaBag :: String -> FilePath -> TestTree
+testMediaBag name odtFile = buildTest $ testMediaBagIO name odtFile
+-}
+--
+
+
+
+namesOfTestsComparingToMarkdown :: [ String ]
+namesOfTestsComparingToMarkdown = [ "bold"
+-- , "citation"
+ , "endnote"
+ , "externalLink"
+ , "footnote"
+ , "headers"
+-- , "horizontalRule"
+ , "italic"
+-- , "listBlocks"
+ , "paragraph"
+ , "strikeout"
+-- , "trackedChanges"
+ , "underlined"
+ ]
+
+namesOfTestsComparingToNative :: [ String ]
+namesOfTestsComparingToNative = [ "blockquote"
+ , "image"
+ , "imageIndex"
+ , "imageWithCaption"
+ , "inlinedCode"
+ , "orderedListMixed"
+ , "orderedListRoman"
+ , "orderedListSimple"
+ , "referenceToChapter"
+ , "referenceToListItem"
+ , "referenceToText"
+ , "simpleTable"
+ , "simpleTableWithCaption"
+-- , "table"
+ , "textMixedStyles"
+ , "tableWithContents"
+ , "unicode"
+ , "unorderedList"
+ ]
diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs
new file mode 100644
index 000000000..de7f14e32
--- /dev/null
+++ b/test/Tests/Readers/Org.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org (tests) where
+
+import Test.Tasty (TestTree, testGroup)
+import qualified Tests.Readers.Org.Block as Block
+import qualified Tests.Readers.Org.Directive as Directive
+import qualified Tests.Readers.Org.Inline as Inline
+import qualified Tests.Readers.Org.Meta as Meta
+
+tests :: [TestTree]
+tests =
+ [ testGroup "Inlines" Inline.tests
+ , testGroup "Basic Blocks" Block.tests
+ , testGroup "Meta Information" Meta.tests
+ , testGroup "Directives" Directive.tests
+ ]
diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs
new file mode 100644
index 000000000..15dc63554
--- /dev/null
+++ b/test/Tests/Readers/Org/Block.hs
@@ -0,0 +1,192 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block (tests) where
+
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+import qualified Tests.Readers.Org.Block.CodeBlock as CodeBlock
+import qualified Tests.Readers.Org.Block.Figure as Figure
+import qualified Tests.Readers.Org.Block.Header as Header
+import qualified Tests.Readers.Org.Block.List as List
+import qualified Tests.Readers.Org.Block.Table as Table
+
+tests :: [TestTree]
+tests =
+ [ "Paragraph" =:
+ "Paragraph\n" =?>
+ para "Paragraph"
+
+ , "Paragraph starting with an asterisk" =:
+ "*five" =?>
+ para "*five"
+
+ , "Paragraph containing asterisk at beginning of line" =:
+ T.unlines [ "lucky"
+ , "*star"
+ ] =?>
+ para ("lucky" <> softbreak <> "*star")
+
+ , "Example block" =:
+ T.unlines [ ": echo hello"
+ , ": echo dear tester"
+ ] =?>
+ codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n"
+
+ , "Example block surrounded by text" =:
+ T.unlines [ "Greetings"
+ , ": echo hello"
+ , ": echo dear tester"
+ , "Bye"
+ ] =?>
+ mconcat [ para "Greetings"
+ , codeBlockWith ("", ["example"], [])
+ "echo hello\necho dear tester\n"
+ , para "Bye"
+ ]
+
+ , "Horizontal Rule" =:
+ T.unlines [ "before"
+ , "-----"
+ , "after"
+ ] =?>
+ mconcat [ para "before"
+ , horizontalRule
+ , para "after"
+ ]
+
+ , "Not a Horizontal Rule" =:
+ "----- em and en dash" =?>
+ para "\8212\8211 em and en dash"
+
+ , "Comment Block" =:
+ T.unlines [ "#+BEGIN_COMMENT"
+ , "stuff"
+ , "bla"
+ , "#+END_COMMENT"] =?>
+ (mempty::Blocks)
+
+ , testGroup "Blocks and fragments"
+ [ "HTML block" =:
+ T.unlines [ "#+BEGIN_HTML"
+ , "<aside>HTML5 is pretty nice.</aside>"
+ , "#+END_HTML"
+ ] =?>
+ rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
+
+ , "Quote block" =:
+ T.unlines [ "#+BEGIN_QUOTE"
+ , "/Niemand/ hat die Absicht, eine Mauer zu errichten!"
+ , "#+END_QUOTE"
+ ] =?>
+ blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
+ , "eine", "Mauer", "zu", "errichten!"
+ ]))
+
+ , "Verse block" =:
+ T.unlines [ "The first lines of Goethe's /Faust/:"
+ , "#+begin_verse"
+ , "Habe nun, ach! Philosophie,"
+ , "Juristerei und Medizin,"
+ , "Und leider auch Theologie!"
+ , "Durchaus studiert, mit heißem Bemühn."
+ , "#+end_verse"
+ ] =?>
+ mconcat
+ [ para $ spcSep [ "The", "first", "lines", "of"
+ , "Goethe's", emph "Faust" <> ":"]
+ , lineBlock
+ [ "Habe nun, ach! Philosophie,"
+ , "Juristerei und Medizin,"
+ , "Und leider auch Theologie!"
+ , "Durchaus studiert, mit heißem Bemühn."
+ ]
+ ]
+
+ , "Verse block with blank lines" =:
+ T.unlines [ "#+BEGIN_VERSE"
+ , "foo"
+ , ""
+ , "bar"
+ , "#+END_VERSE"
+ ] =?>
+ lineBlock [ "foo", mempty, "bar" ]
+
+ , "Verse block with varying indentation" =:
+ T.unlines [ "#+BEGIN_VERSE"
+ , " hello darkness"
+ , "my old friend"
+ , "#+END_VERSE"
+ ] =?>
+ lineBlock [ "\160\160hello darkness", "my old friend" ]
+
+ , "Raw block LaTeX" =:
+ T.unlines [ "#+BEGIN_LaTeX"
+ , "The category $\\cat{Set}$ is adhesive."
+ , "#+END_LaTeX"
+ ] =?>
+ rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n"
+
+ , "Raw LaTeX line" =:
+ "#+LATEX: \\let\\foo\\bar" =?>
+ rawBlock "latex" "\\let\\foo\\bar"
+
+ , "Raw Beamer line" =:
+ "#+beamer: \\pause" =?>
+ rawBlock "beamer" "\\pause"
+
+ , "Raw HTML line" =:
+ "#+HTML: <aside>not important</aside>" =?>
+ rawBlock "html" "<aside>not important</aside>"
+
+ , "Export block HTML" =:
+ T.unlines [ "#+BEGIN_export html"
+ , "<samp>Hello, World!</samp>"
+ , "#+END_export"
+ ] =?>
+ rawBlock "html" "<samp>Hello, World!</samp>\n"
+
+ , "LaTeX fragment" =:
+ T.unlines [ "\\begin{equation}"
+ , "X_i = \\begin{cases}"
+ , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
+ , " C_{\\alpha(i)} & \\text{otherwise}"
+ , " \\end{cases}"
+ , "\\end{equation}"
+ ] =?>
+ rawBlock "latex"
+ (unlines [ "\\begin{equation}"
+ , "X_i = \\begin{cases}"
+ , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <>
+ " \\alpha(i)\\\\"
+ , " C_{\\alpha(i)} & \\text{otherwise}"
+ , " \\end{cases}"
+ , "\\end{equation}"
+ ])
+
+ , "Convert blank lines in blocks to single newlines" =:
+ T.unlines [ "#+begin_html"
+ , ""
+ , "<span>boring</span>"
+ , ""
+ , "#+end_html"
+ ] =?>
+ rawBlock "html" "\n<span>boring</span>\n\n"
+
+ , "Accept `ATTR_HTML` attributes for generic block" =:
+ T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code"
+ , "#+BEGIN_TEST"
+ , "nonsense"
+ , "#+END_TEST"
+ ] =?>
+ let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")])
+ in divWith attr (para "nonsense")
+ ]
+
+ , testGroup "Headers" Header.tests
+ , testGroup "Figures" Figure.tests
+ , testGroup "Lists" List.tests
+ , testGroup "CodeBlocks" CodeBlock.tests
+ , testGroup "Tables" Table.tests
+ ]
diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs
new file mode 100644
index 000000000..8fa822089
--- /dev/null
+++ b/test/Tests/Readers/Org/Block/CodeBlock.hs
@@ -0,0 +1,194 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block.CodeBlock (tests) where
+
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "Source block" =:
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" <>
+ " where greeting = \"moin\"\n"
+ in codeBlockWith attr' code'
+
+ , "Source block with indented code" =:
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" <>
+ " where greeting = \"moin\"\n"
+ in codeBlockWith attr' code'
+
+ , "Source block with tab-indented code" =:
+ T.unlines [ "\t#+BEGIN_SRC haskell"
+ , "\tmain = putStrLn greeting"
+ , "\t where greeting = \"moin\""
+ , "\t#+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" <>
+ " where greeting = \"moin\"\n"
+ in codeBlockWith attr' code'
+
+ , "Empty source block" =:
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = ""
+ in codeBlockWith attr' code'
+
+ , "Source block between paragraphs" =:
+ T.unlines [ "Low German greeting"
+ , " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"Moin!\""
+ , " #+END_SRC" ] =?>
+ let attr' = ("", ["haskell"], [])
+ code' = "main = putStrLn greeting\n" <>
+ " where greeting = \"Moin!\"\n"
+ in mconcat [ para $ spcSep [ "Low", "German", "greeting" ]
+ , codeBlockWith attr' code'
+ ]
+ , "Source block with babel arguments" =:
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC" ] =?>
+ let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax
+ params = [ ("org-language", "emacs-lisp")
+ , ("exports", "both")
+ ]
+ code' = unlines [ "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))" ]
+ in codeBlockWith ("", classes, params) code'
+
+ , "Source block with results and :exports both" =:
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65"] =?>
+ let classes = [ "commonlisp" ]
+ params = [ ("org-language", "emacs-lisp")
+ , ("exports", "both")
+ ]
+ code' = unlines [ "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))" ]
+ results' = "65\n"
+ in codeBlockWith ("", classes, params) code'
+ <>
+ codeBlockWith ("", ["example"], []) results'
+
+ , "Source block with results and :exports code" =:
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
+ let classes = [ "commonlisp" ]
+ params = [ ("org-language", "emacs-lisp")
+ , ("exports", "code")
+ ]
+ code' = unlines [ "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))" ]
+ in codeBlockWith ("", classes, params) code'
+
+ , "Source block with results and :exports results" =:
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
+ let results' = "65\n"
+ in codeBlockWith ("", ["example"], []) results'
+
+ , "Source block with results and :exports none" =:
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
+ (mempty :: Blocks)
+
+ , "Source block with toggling header arguments" =:
+ T.unlines [ "#+BEGIN_SRC sh :noeval"
+ , "echo $HOME"
+ , "#+END_SRC"
+ ] =?>
+ let classes = [ "bash" ]
+ params = [ ("org-language", "sh"), ("noeval", "yes") ]
+ in codeBlockWith ("", classes, params) "echo $HOME\n"
+
+ , "Source block with line number switch" =:
+ T.unlines [ "#+BEGIN_SRC sh -n 10"
+ , ":() { :|:& };:"
+ , "#+END_SRC"
+ ] =?>
+ let classes = [ "bash", "numberLines" ]
+ params = [ ("org-language", "sh"), ("startFrom", "10") ]
+ in codeBlockWith ("", classes, params) ":() { :|:& };:\n"
+
+ , "Source block with multi-word parameter values" =:
+ T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng "
+ , "digraph { id [label=\"ID\"] }"
+ , "#+END_SRC"
+ ] =?>
+ let classes = [ "dot" ]
+ params = [ ("cmdline", "-Kdot -Tpng") ]
+ in codeBlockWith ("", classes, params) "digraph { id [label=\"ID\"] }\n"
+
+ , "Example block" =:
+ T.unlines [ "#+begin_example"
+ , "A chosen representation of"
+ , "a rule."
+ , "#+eND_exAMPle"
+ ] =?>
+ codeBlockWith ("", ["example"], [])
+ "A chosen representation of\na rule.\n"
+
+ , "Code block with caption" =:
+ T.unlines [ "#+CAPTION: Functor laws in Haskell"
+ , "#+NAME: functor-laws"
+ , "#+BEGIN_SRC haskell"
+ , "fmap id = id"
+ , "fmap (p . q) = (fmap p) . (fmap q)"
+ , "#+END_SRC"
+ ] =?>
+ divWith
+ nullAttr
+ (mappend
+ (plain $ spanWith ("", ["label"], [])
+ (spcSep [ "Functor", "laws", "in", "Haskell" ]))
+ (codeBlockWith ("functor-laws", ["haskell"], [])
+ (unlines [ "fmap id = id"
+ , "fmap (p . q) = (fmap p) . (fmap q)"
+ ])))
+
+ , "Non-letter chars in source block parameters" =:
+ T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich"
+ , "code body"
+ , "#+END_SRC"
+ ] =?>
+ let params = [ ("org-language", "C")
+ , ("tangle", "xxxx.c")
+ , ("city", "Zürich")
+ ]
+ in codeBlockWith ( "", ["c"], params) "code body\n"
+ ]
diff --git a/test/Tests/Readers/Org/Block/Figure.hs b/test/Tests/Readers/Org/Block/Figure.hs
new file mode 100644
index 000000000..cae6ef179
--- /dev/null
+++ b/test/Tests/Readers/Org/Block/Figure.hs
@@ -0,0 +1,57 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block.Figure (tests) where
+
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:))
+import Text.Pandoc.Builder (image, imageWith, para)
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "Figure" =:
+ T.unlines [ "#+caption: A very courageous man."
+ , "#+name: goodguy"
+ , "[[file:edward.jpg]]"
+ ] =?>
+ para (image "edward.jpg" "fig:goodguy" "A very courageous man.")
+
+ , "Figure with no name" =:
+ T.unlines [ "#+caption: I've been through the desert on this"
+ , "[[file:horse.png]]"
+ ] =?>
+ para (image "horse.png" "fig:" "I've been through the desert on this")
+
+ , "Figure with `fig:` prefix in name" =:
+ T.unlines [ "#+caption: Used as a metapher in evolutionary biology."
+ , "#+name: fig:redqueen"
+ , "[[./the-red-queen.jpg]]"
+ ] =?>
+ para (image "./the-red-queen.jpg" "fig:redqueen"
+ "Used as a metapher in evolutionary biology.")
+
+ , "Figure with HTML attributes" =:
+ T.unlines [ "#+CAPTION: mah brain just explodid"
+ , "#+NAME: lambdacat"
+ , "#+ATTR_HTML: :style color: blue :role button"
+ , "[[file:lambdacat.jpg]]"
+ ] =?>
+ let kv = [("style", "color: blue"), ("role", "button")]
+ name = "fig:lambdacat"
+ caption = "mah brain just explodid"
+ in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption)
+
+ , "Labelled figure" =:
+ T.unlines [ "#+CAPTION: My figure"
+ , "#+LABEL: fig:myfig"
+ , "[[file:blub.png]]"
+ ] =?>
+ let attr = ("fig:myfig", mempty, mempty)
+ in para (imageWith attr "blub.png" "fig:" "My figure")
+
+ , "Figure with empty caption" =:
+ T.unlines [ "#+CAPTION:"
+ , "[[file:guess.jpg]]"
+ ] =?>
+ para (image "guess.jpg" "fig:" "")
+ ]
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
new file mode 100644
index 000000000..e8ad88558
--- /dev/null
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -0,0 +1,182 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block.Header (tests) where
+
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep, tagSpan)
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "First Level Header" =:
+ "* Headline\n" =?>
+ headerWith ("headline", [], []) 1 "Headline"
+
+ , "Third Level Header" =:
+ "*** Third Level Headline\n" =?>
+ headerWith ("third-level-headline", [], [])
+ 3
+ ("Third" <> space <> "Level" <> space <> "Headline")
+
+ , "Compact Headers with Paragraph" =:
+ T.unlines [ "* First Level"
+ , "** Second Level"
+ , " Text"
+ ] =?>
+ mconcat [ headerWith ("first-level", [], [])
+ 1
+ ("First" <> space <> "Level")
+ , headerWith ("second-level", [], [])
+ 2
+ ("Second" <> space <> "Level")
+ , para "Text"
+ ]
+
+ , "Separated Headers with Paragraph" =:
+ T.unlines [ "* First Level"
+ , ""
+ , "** Second Level"
+ , ""
+ , " Text"
+ ] =?>
+ mconcat [ headerWith ("first-level", [], [])
+ 1
+ ("First" <> space <> "Level")
+ , headerWith ("second-level", [], [])
+ 2
+ ("Second" <> space <> "Level")
+ , para "Text"
+ ]
+
+ , "Headers not preceded by a blank line" =:
+ T.unlines [ "** eat dinner"
+ , "Spaghetti and meatballs tonight."
+ , "** walk dog"
+ ] =?>
+ mconcat [ headerWith ("eat-dinner", [], [])
+ 2
+ ("eat" <> space <> "dinner")
+ , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ]
+ , headerWith ("walk-dog", [], [])
+ 2
+ ("walk" <> space <> "dog")
+ ]
+
+ , testGroup "Todo keywords"
+ [ "Header with known todo keyword" =:
+ "* TODO header" =?>
+ let todoSpan = spanWith ("", ["todo", "TODO"], []) "TODO"
+ in headerWith ("header", [], []) 1 (todoSpan <> space <> "header")
+
+ , "Header marked as done" =:
+ "* DONE header" =?>
+ let todoSpan = spanWith ("", ["done", "DONE"], []) "DONE"
+ in headerWith ("header", [], []) 1 (todoSpan <> space <> "header")
+
+ , "Header with unknown todo keyword" =:
+ "* WAITING header" =?>
+ headerWith ("waiting-header", [], []) 1 "WAITING header"
+
+ , "Custom todo keywords" =:
+ T.unlines [ "#+TODO: WAITING CANCELLED"
+ , "* WAITING compile"
+ , "* CANCELLED lunch"
+ ] =?>
+ let todoSpan = spanWith ("", ["todo", "WAITING"], []) "WAITING"
+ doneSpan = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED"
+ in headerWith ("compile", [], []) 1 (todoSpan <> space <> "compile")
+ <> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch")
+
+ , "Custom todo keywords with multiple done-states" =:
+ T.unlines [ "#+TODO: WAITING | DONE CANCELLED "
+ , "* WAITING compile"
+ , "* CANCELLED lunch"
+ , "* DONE todo-feature"
+ ] =?>
+ let waiting = spanWith ("", ["todo", "WAITING"], []) "WAITING"
+ cancelled = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED"
+ done = spanWith ("", ["done", "DONE"], []) "DONE"
+ in headerWith ("compile", [], []) 1 (waiting <> space <> "compile")
+ <> headerWith ("lunch", [], []) 1 (cancelled <> space <> "lunch")
+ <> headerWith ("todo-feature", [], []) 1 (done <> space <> "todo-feature")
+ ]
+
+ , "Tagged headers" =:
+ T.unlines [ "* Personal :PERSONAL:"
+ , "** Call Mom :@PHONE:"
+ , "** Call John :@PHONE:JOHN: "
+ ] =?>
+ mconcat [ headerWith ("personal", [], [])
+ 1
+ ("Personal " <> tagSpan "PERSONAL")
+ , headerWith ("call-mom", [], [])
+ 2
+ ("Call Mom " <> tagSpan "@PHONE")
+ , headerWith ("call-john", [], [])
+ 2
+ ("Call John " <> tagSpan "@PHONE" <> "\160" <> tagSpan "JOHN")
+ ]
+
+ , "Untagged header containing colons" =:
+ "* This: is not: tagged" =?>
+ headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged"
+
+ , "Header starting with strokeout text" =:
+ T.unlines [ "foo"
+ , ""
+ , "* +thing+ other thing"
+ ] =?>
+ mconcat [ para "foo"
+ , headerWith ("thing-other-thing", [], [])
+ 1
+ (strikeout "thing" <> " other thing")
+ ]
+
+ , "Comment Trees" =:
+ T.unlines [ "* COMMENT A comment tree"
+ , " Not much going on here"
+ , "** This will be dropped"
+ , "* Comment tree above"
+ ] =?>
+ headerWith ("comment-tree-above", [], []) 1 "Comment tree above"
+
+ , "Nothing but a COMMENT header" =:
+ "* COMMENT Test" =?>
+ (mempty::Blocks)
+
+ , "Tree with :noexport:" =:
+ T.unlines [ "* Should be ignored :archive:noexport:old:"
+ , "** Old stuff"
+ , " This is not going to be exported"
+ ] =?>
+ (mempty::Blocks)
+
+ , "Subtree with :noexport:" =:
+ T.unlines [ "* Exported"
+ , "** This isn't exported :noexport:"
+ , "*** This neither"
+ , "** But this is"
+ ] =?>
+ mconcat [ headerWith ("exported", [], []) 1 "Exported"
+ , headerWith ("but-this-is", [], []) 2 "But this is"
+ ]
+
+ , "Preferences are treated as header attributes" =:
+ T.unlines [ "* foo"
+ , " :PROPERTIES:"
+ , " :custom_id: fubar"
+ , " :bar: baz"
+ , " :END:"
+ ] =?>
+ headerWith ("fubar", [], [("bar", "baz")]) 1 "foo"
+
+
+ , "Headers marked with a unnumbered property get a class of the same name" =:
+ T.unlines [ "* Not numbered"
+ , " :PROPERTIES:"
+ , " :UNNUMBERED: t"
+ , " :END:"
+ ] =?>
+ headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
+ ]
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
new file mode 100644
index 000000000..343682a80
--- /dev/null
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -0,0 +1,244 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block.List (tests) where
+
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "Simple Bullet Lists" =:
+ ("- Item1\n" <>
+ "- Item2\n") =?>
+ bulletList [ plain "Item1"
+ , plain "Item2"
+ ]
+
+ , "Indented Bullet Lists" =:
+ (" - Item1\n" <>
+ " - Item2\n") =?>
+ bulletList [ plain "Item1"
+ , plain "Item2"
+ ]
+
+ , "Unindented *" =:
+ ("- Item1\n" <>
+ "* Item2\n") =?>
+ bulletList [ plain "Item1"
+ ] <>
+ headerWith ("item2", [], []) 1 "Item2"
+
+ , "Multi-line Bullet Lists" =:
+ ("- *Fat\n" <>
+ " Tony*\n" <>
+ "- /Sideshow\n" <>
+ " Bob/") =?>
+ bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony")
+ , plain $ emph ("Sideshow" <> softbreak <> "Bob")
+ ]
+
+ , "Nested Bullet Lists" =:
+ ("- Discovery\n" <>
+ " + One More Time\n" <>
+ " + Harder, Better, Faster, Stronger\n" <>
+ "- Homework\n" <>
+ " + Around the World\n"<>
+ "- Human After All\n" <>
+ " + Technologic\n" <>
+ " + Robot Rock\n") =?>
+ bulletList [ mconcat
+ [ plain "Discovery"
+ , bulletList [ plain ("One" <> space <>
+ "More" <> space <>
+ "Time")
+ , plain ("Harder," <> space <>
+ "Better," <> space <>
+ "Faster," <> space <>
+ "Stronger")
+ ]
+ ]
+ , mconcat
+ [ plain "Homework"
+ , bulletList [ plain ("Around" <> space <>
+ "the" <> space <>
+ "World")
+ ]
+ ]
+ , mconcat
+ [ plain ("Human" <> space <> "After" <> space <> "All")
+ , bulletList [ plain "Technologic"
+ , plain ("Robot" <> space <> "Rock")
+ ]
+ ]
+ ]
+
+ , "Bullet List with Decreasing Indent" =:
+ " - Discovery\n\
+ \ - Human After All\n" =?>
+ mconcat [ bulletList [ plain "Discovery" ]
+ , bulletList [ plain ("Human" <> space <> "After" <> space <> "All")]
+ ]
+
+ , "Header follows Bullet List" =:
+ " - Discovery\n\
+ \ - Human After All\n\
+ \* Homework" =?>
+ mconcat [ bulletList [ plain "Discovery"
+ , plain ("Human" <> space <> "After" <> space <> "All")
+ ]
+ , headerWith ("homework", [], []) 1 "Homework"
+ ]
+
+ , "Bullet List Unindented with trailing Header" =:
+ "- Discovery\n\
+ \- Homework\n\
+ \* NotValidListItem" =?>
+ mconcat [ bulletList [ plain "Discovery"
+ , plain "Homework"
+ ]
+ , headerWith ("notvalidlistitem", [], []) 1 "NotValidListItem"
+ ]
+
+ , "Empty bullet points" =:
+ T.unlines [ "-"
+ , "- "
+ ] =?>
+ bulletList [ plain "", plain "" ]
+
+ , "Simple Ordered List" =:
+ ("1. Item1\n" <>
+ "2. Item2\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ plain "Item1"
+ , plain "Item2"
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Simple Ordered List with Parens" =:
+ ("1) Item1\n" <>
+ "2) Item2\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ plain "Item1"
+ , plain "Item2"
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Indented Ordered List" =:
+ (" 1. Item1\n" <>
+ " 2. Item2\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ plain "Item1"
+ , plain "Item2"
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Empty ordered list item" =:
+ T.unlines [ "1."
+ , "3. "
+ ] =?>
+ orderedList [ plain "", plain "" ]
+
+ , "Nested Ordered Lists" =:
+ ("1. One\n" <>
+ " 1. One-One\n" <>
+ " 2. One-Two\n" <>
+ "2. Two\n" <>
+ " 1. Two-One\n"<>
+ " 2. Two-Two\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ mconcat
+ [ plain "One"
+ , orderedList [ plain "One-One"
+ , plain "One-Two"
+ ]
+ ]
+ , mconcat
+ [ plain "Two"
+ , orderedList [ plain "Two-One"
+ , plain "Two-Two"
+ ]
+ ]
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Ordered List in Bullet List" =:
+ ("- Emacs\n" <>
+ " 1. Org\n") =?>
+ bulletList [ plain "Emacs" <>
+ orderedList [ plain "Org"]
+ ]
+
+ , "Bullet List in Ordered List" =:
+ ("1. GNU\n" <>
+ " - Freedom\n") =?>
+ orderedList [ plain "GNU" <> bulletList [ plain "Freedom" ] ]
+
+ , "Definition List" =:
+ T.unlines [ "- PLL :: phase-locked loop"
+ , "- TTL ::"
+ , " transistor-transistor logic"
+ , "- PSK :: phase-shift keying"
+ , ""
+ , " a digital modulation scheme"
+ ] =?>
+ definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ])
+ , ("TTL", [ plain $ "transistor-transistor" <> space <>
+ "logic" ])
+ , ("PSK", [ mconcat
+ [ para $ "phase-shift" <> space <> "keying"
+ , para $ spcSep [ "a", "digital"
+ , "modulation", "scheme" ]
+ ]
+ ])
+ ]
+ , "Definition list with multi-word term" =:
+ " - Elijah Wood :: He plays Frodo" =?>
+ definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])]
+ , "Compact definition list" =:
+ T.unlines [ "- ATP :: adenosine 5' triphosphate"
+ , "- DNA :: deoxyribonucleic acid"
+ , "- PCR :: polymerase chain reaction"
+ , ""
+ ] =?>
+ definitionList
+ [ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ])
+ , ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ])
+ , ("PCR", [ plain $ spcSep [ "polymerase", "chain", "reaction" ] ])
+ ]
+
+ , "Definition List With Trailing Header" =:
+ "- definition :: list\n\
+ \- cool :: defs\n\
+ \* header" =?>
+ mconcat [ definitionList [ ("definition", [plain "list"])
+ , ("cool", [plain "defs"])
+ ]
+ , headerWith ("header", [], []) 1 "header"
+ ]
+
+ , "Definition lists double-colon markers must be surrounded by whitespace" =:
+ "- std::cout" =?>
+ bulletList [ plain "std::cout" ]
+
+ , "Loose bullet list" =:
+ T.unlines [ "- apple"
+ , ""
+ , "- orange"
+ , ""
+ , "- peach"
+ ] =?>
+ bulletList [ para "apple"
+ , para "orange"
+ , para "peach"
+ ]
+
+ , "Recognize preceding paragraphs in non-list contexts" =:
+ T.unlines [ "CLOSED: [2015-10-19 Mon 15:03]"
+ , "- Note taken on [2015-10-19 Mon 13:24]"
+ ] =?>
+ mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]"
+ , bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ]
+ ]
+ ]
diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs
new file mode 100644
index 000000000..db6e756f8
--- /dev/null
+++ b/test/Tests/Readers/Org/Block/Table.hs
@@ -0,0 +1,150 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Block.Table (tests) where
+
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+simpleTable' :: Int
+ -> [Blocks]
+ -> [[Blocks]]
+ -> Blocks
+simpleTable' n = table "" (replicate n (AlignDefault, 0.0))
+
+tests :: [TestTree]
+tests =
+ [ "Single cell table" =:
+ "|Test|" =?>
+ simpleTable' 1 mempty [[plain "Test"]]
+
+ , "Multi cell table" =:
+ "| One | Two |" =?>
+ simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
+
+ , "Multi line table" =:
+ T.unlines [ "| One |"
+ , "| Two |"
+ , "| Three |"
+ ] =?>
+ simpleTable' 1 mempty
+ [ [ plain "One" ]
+ , [ plain "Two" ]
+ , [ plain "Three" ]
+ ]
+
+ , "Empty table" =:
+ "||" =?>
+ simpleTable' 1 mempty [[mempty]]
+
+ , "Glider Table" =:
+ T.unlines [ "| 1 | 0 | 0 |"
+ , "| 0 | 1 | 1 |"
+ , "| 1 | 1 | 0 |"
+ ] =?>
+ simpleTable' 3 mempty
+ [ [ plain "1", plain "0", plain "0" ]
+ , [ plain "0", plain "1", plain "1" ]
+ , [ plain "1", plain "1", plain "0" ]
+ ]
+
+ , "Table between Paragraphs" =:
+ T.unlines [ "Before"
+ , "| One | Two |"
+ , "After"
+ ] =?>
+ mconcat [ para "Before"
+ , simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
+ , para "After"
+ ]
+
+ , "Table with Header" =:
+ T.unlines [ "| Species | Status |"
+ , "|--------------+--------------|"
+ , "| cervisiae | domesticated |"
+ , "| paradoxus | wild |"
+ ] =?>
+ simpleTable [ plain "Species", plain "Status" ]
+ [ [ plain "cervisiae", plain "domesticated" ]
+ , [ plain "paradoxus", plain "wild" ]
+ ]
+
+ , "Table with final hline" =:
+ T.unlines [ "| cervisiae | domesticated |"
+ , "| paradoxus | wild |"
+ , "|--------------+--------------|"
+ ] =?>
+ simpleTable' 2 mempty
+ [ [ plain "cervisiae", plain "domesticated" ]
+ , [ plain "paradoxus", plain "wild" ]
+ ]
+
+ , "Table in a box" =:
+ T.unlines [ "|---------|---------|"
+ , "| static | Haskell |"
+ , "| dynamic | Lisp |"
+ , "|---------+---------|"
+ ] =?>
+ simpleTable' 2 mempty
+ [ [ plain "static", plain "Haskell" ]
+ , [ plain "dynamic", plain "Lisp" ]
+ ]
+
+ , "Table with empty cells" =:
+ "|||c|" =?>
+ simpleTable' 3 mempty [[mempty, mempty, plain "c"]]
+
+ , "Table with empty rows" =:
+ T.unlines [ "| first |"
+ , "| |"
+ , "| third |"
+ ] =?>
+ simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]]
+
+ , "Table with alignment row" =:
+ T.unlines [ "| Numbers | Text | More |"
+ , "| <c> | <r> | |"
+ , "| 1 | One | foo |"
+ , "| 2 | Two | bar |"
+ ] =?>
+ table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
+ []
+ [ [ plain "Numbers", plain "Text", plain "More" ]
+ , [ plain "1" , plain "One" , plain "foo" ]
+ , [ plain "2" , plain "Two" , plain "bar" ]
+ ]
+
+ , "Pipe within text doesn't start a table" =:
+ "Ceci n'est pas une | pipe " =?>
+ para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ])
+
+ , "Missing pipe at end of row" =:
+ "|incomplete-but-valid" =?>
+ simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ]
+
+ , "Table with differing row lengths" =:
+ T.unlines [ "| Numbers | Text "
+ , "|-"
+ , "| <c> | <r> |"
+ , "| 1 | One | foo |"
+ , "| 2"
+ ] =?>
+ table "" (zip [AlignCenter, AlignRight] [0, 0])
+ [ plain "Numbers", plain "Text" ]
+ [ [ plain "1" , plain "One" , plain "foo" ]
+ , [ plain "2" ]
+ ]
+
+ , "Table with caption" =:
+ T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
+ , "| x | 6 |"
+ , "| 9 | 42 |"
+ ] =?>
+ table "Hitchhiker's Multiplication Table"
+ [(AlignDefault, 0), (AlignDefault, 0)]
+ []
+ [ [ plain "x", plain "6" ]
+ , [ plain "9", plain "42" ]
+ ]
+ ]
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
new file mode 100644
index 000000000..7e2c0fb8d
--- /dev/null
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -0,0 +1,199 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Directive (tests) where
+
+import Data.Time (UTCTime (UTCTime), secondsToDiffTime)
+import Data.Time.Calendar (Day (ModifiedJulianDay))
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>), ToString, purely, test)
+import Tests.Readers.Org.Shared ((=:), tagSpan)
+import Text.Pandoc
+import Text.Pandoc.Builder
+import qualified Data.ByteString as BS
+import qualified Data.Text as T
+
+testWithFiles :: (ToString c)
+ => [(FilePath, BS.ByteString)]
+ -> String -- ^ name of test case
+ -> (T.Text, c) -- ^ (input, expected value)
+ -> TestTree
+testWithFiles fileDefs = test (orgWithFiles fileDefs)
+ where
+orgWithFiles :: [(FilePath, BS.ByteString)] -> T.Text -> Pandoc
+orgWithFiles fileDefs input =
+ let readOrg' = readOrg def{ readerExtensions = getDefaultExtensions "org" }
+ in flip purely input $ \inp -> do
+ modifyPureState (\st -> st { stFiles = files fileDefs })
+ readOrg' inp
+
+
+files :: [(FilePath, BS.ByteString)] -> FileTree
+files fileDefs =
+ let dummyTime = UTCTime (ModifiedJulianDay 125) (secondsToDiffTime 0)
+ in foldr (\(fp, bs) -> insertInFileTree fp (FileInfo dummyTime bs))
+ mempty fileDefs
+
+tests :: [TestTree]
+tests =
+ [ testGroup "export options"
+ [ "disable simple sub/superscript syntax" =:
+ T.unlines [ "#+OPTIONS: ^:nil"
+ , "a^b"
+ ] =?>
+ para "a^b"
+
+ , "directly select drawers to be exported" =:
+ T.unlines [ "#+OPTIONS: d:(\"IMPORTANT\")"
+ , ":IMPORTANT:"
+ , "23"
+ , ":END:"
+ , ":BORING:"
+ , "very boring"
+ , ":END:"
+ ] =?>
+ divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "23")
+
+ , "exclude drawers from being exported" =:
+ T.unlines [ "#+OPTIONS: d:(not \"BORING\")"
+ , ":IMPORTANT:"
+ , "5"
+ , ":END:"
+ , ":BORING:"
+ , "very boring"
+ , ":END:"
+ ] =?>
+ divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "5")
+
+ , "don't include archive trees" =:
+ T.unlines [ "#+OPTIONS: arch:nil"
+ , "* old :ARCHIVE:"
+ ] =?>
+ (mempty ::Blocks)
+
+ , "include complete archive trees" =:
+ T.unlines [ "#+OPTIONS: arch:t"
+ , "* old :ARCHIVE:"
+ , " boring"
+ ] =?>
+ mconcat [ headerWith ("old", [], mempty) 1
+ ("old" <> space <> tagSpan "ARCHIVE")
+ , para "boring"
+ ]
+
+ , "include archive tree header only" =:
+ T.unlines [ "#+OPTIONS: arch:headline"
+ , "* old :ARCHIVE:"
+ , " boring"
+ ] =?>
+ headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE")
+
+ , "limit headline depth" =:
+ T.unlines [ "#+OPTIONS: H:2"
+ , "* top-level section"
+ , "** subsection"
+ , "*** list item 1"
+ , "*** list item 2"
+ ] =?>
+ mconcat [ headerWith ("top-level-section", [], []) 1 "top-level section"
+ , headerWith ("subsection", [], []) 2 "subsection"
+ , orderedList [ para "list item 1", para "list item 2" ]
+ ]
+
+ , "turn all headlines into lists" =:
+ T.unlines [ "#+OPTIONS: H:0"
+ , "first block"
+ , "* top-level section 1"
+ , "** subsection"
+ , "* top-level section 2"
+ ] =?>
+ mconcat [ para "first block"
+ , orderedList
+ [ para "top-level section 1" <>
+ orderedList [ para "subsection" ]
+ , para "top-level section 2" ]
+ ]
+
+ , "preserve linebreaks as hard breaks" =:
+ T.unlines [ "#+OPTIONS: \\n:t"
+ , "first"
+ , "second"
+ ] =?>
+ para ("first" <> linebreak <> "second")
+
+ , "disable author export" =:
+ T.unlines [ "#+OPTIONS: author:nil"
+ , "#+AUTHOR: ShyGuy"
+ ] =?>
+ Pandoc nullMeta mempty
+
+ , "disable creator export" =:
+ T.unlines [ "#+OPTIONS: creator:nil"
+ , "#+creator: The Architect"
+ ] =?>
+ Pandoc nullMeta mempty
+
+ , "disable email export" =:
+ T.unlines [ "#+OPTIONS: email:nil"
+ , "#+email: no-mail-please@example.com"
+ ] =?>
+ Pandoc nullMeta mempty
+
+ , "disable inclusion of todo keywords" =:
+ T.unlines [ "#+OPTIONS: todo:nil"
+ , "** DONE todo export"
+ ] =?>
+ headerWith ("todo-export", [], []) 2 "todo export"
+
+ , "remove tags from headlines" =:
+ T.unlines [ "#+OPTIONS: tags:nil"
+ , "* Headline :hello:world:"
+ ] =?>
+ headerWith ("headline", [], mempty) 1 "Headline"
+ ]
+
+ , testGroup "Include"
+ [ testWithFiles [("./other.org", "content of other file\n")]
+ "file inclusion"
+ (T.unlines [ "#+include: \"other.org\"" ] =?>
+ plain "content of other file")
+
+ , testWithFiles [("./world.org", "World\n\n")]
+ "Included file belongs to item"
+ (T.unlines [ "- Hello,\n #+include: \"world.org\"" ] =?>
+ bulletList [para "Hello," <> para "World"])
+
+ , testWithFiles [("./level3.org", "*** Level3\n\n")]
+ "Default include preserves level"
+ (T.unlines [ "#+include: \"level3.org\"" ] =?>
+ headerWith ("level3", [], []) 3 "Level3")
+
+ , testWithFiles [("./level3.org", "*** Level3\n\n")]
+ "Minlevel shifts level"
+ (T.unlines [ "#+include: \"level3.org\" :minlevel 1" ] =?>
+ headerWith ("level3", [], []) 1 "Level3")
+
+ , testWithFiles [("./src.hs", "putStrLn outString\n")]
+ "Include file as source code snippet"
+ (T.unlines [ "#+include: \"src.hs\" src haskell" ] =?>
+ codeBlockWith ("", ["haskell"], []) "putStrLn outString\n")
+
+ , testWithFiles [("./export-latex.org", "\\emph{Hello}\n")]
+ "Include file as export snippet"
+ (T.unlines [ "#+include: \"export-latex.org\" export latex" ] =?>
+ rawBlock "latex" "\\emph{Hello}\n")
+
+ , testWithFiles [("./subdir/foo-bar.latex", "foo\n"),
+ ("./hello.lisp", "(print \"Hello!\")\n")
+ ]
+ "include directive is limited to one line"
+ (T.unlines [ "#+INCLUDE: \"hello.lisp\" src lisp"
+ , "#+include: \"subdir/foo-bar.latex\" export latex"
+ , "bar"
+ ] =?>
+ mconcat
+ [ codeBlockWith ("", ["lisp"], []) "(print \"Hello!\")\n"
+ , rawBlock "latex" "foo\n"
+ , para "bar"
+ ]
+ )
+ ]
+ ]
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
new file mode 100644
index 000000000..9bf5556d2
--- /dev/null
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -0,0 +1,352 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Inline (tests) where
+
+import Data.List (intersperse)
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc.Builder
+import Text.Pandoc.Shared (underlineSpan)
+import qualified Data.Text as T
+import qualified Tests.Readers.Org.Inline.Citation as Citation
+import qualified Tests.Readers.Org.Inline.Note as Note
+import qualified Tests.Readers.Org.Inline.Smart as Smart
+
+tests :: [TestTree]
+tests =
+ [ "Plain String" =:
+ "Hello, World" =?>
+ para (spcSep [ "Hello,", "World" ])
+
+ , "Emphasis" =:
+ "/Planet Punk/" =?>
+ para (emph . spcSep $ ["Planet", "Punk"])
+
+ , "Strong" =:
+ "*Cider*" =?>
+ para (strong "Cider")
+
+ , "Strong Emphasis" =:
+ "/*strength*/" =?>
+ para (emph . strong $ "strength")
+
+ , "Emphasized Strong preceded by space" =:
+ " */super/*" =?>
+ para (strong . emph $ "super")
+
+ , "Underline" =:
+ "_underline_" =?>
+ para (underlineSpan "underline")
+
+ , "Strikeout" =:
+ "+Kill Bill+" =?>
+ para (strikeout . spcSep $ [ "Kill", "Bill" ])
+
+ , "Verbatim" =:
+ "=Robot.rock()=" =?>
+ para (code "Robot.rock()")
+
+ , "Code" =:
+ "~word for word~" =?>
+ para (code "word for word")
+
+ , "Math $..$" =:
+ "$E=mc^2$" =?>
+ para (math "E=mc^2")
+
+ , "Math $$..$$" =:
+ "$$E=mc^2$$" =?>
+ para (displayMath "E=mc^2")
+
+ , "Math \\[..\\]" =:
+ "\\[E=ℎν\\]" =?>
+ para (displayMath "E=ℎν")
+
+ , "Math \\(..\\)" =:
+ "\\(σ_x σ_p ≥ \\frac{ℏ}{2}\\)" =?>
+ para (math "σ_x σ_p ≥ \\frac{ℏ}{2}")
+
+ , "Symbol" =:
+ "A * symbol" =?>
+ para (str "A" <> space <> str "*" <> space <> "symbol")
+
+ , "Superscript simple expression" =:
+ "2^-λ" =?>
+ para (str "2" <> superscript "-λ")
+
+ , "Superscript multi char" =:
+ "2^{n-1}" =?>
+ para (str "2" <> superscript "n-1")
+
+ , "Subscript simple expression" =:
+ "a_n" =?>
+ para (str "a" <> subscript "n")
+
+ , "Subscript multi char" =:
+ "a_{n+1}" =?>
+ para (str "a" <> subscript "n+1")
+
+ , "Linebreak" =:
+ "line \\\\ \nbreak" =?>
+ para ("line" <> linebreak <> "break")
+
+ , "Inline note" =:
+ "[fn::Schreib mir eine E-Mail]" =?>
+ para (note $ para "Schreib mir eine E-Mail")
+
+ , "Markup-chars not occuring on word break are symbols" =:
+ T.unlines [ "this+that+ +so+on"
+ , "seven*eight* nine*"
+ , "+not+funny+"
+ ] =?>
+ para ("this+that+ +so+on" <> softbreak <>
+ "seven*eight* nine*" <> softbreak <>
+ strikeout "not+funny")
+
+ , "No empty markup" =:
+ "// ** __ <> == ~~ $$" =?>
+ para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ])
+
+ , "Adherence to Org's rules for markup borders" =:
+ "/t/& a/ / ./r/ (*l*) /e/! /b/." =?>
+ para (spcSep [ emph $ "t/&" <> space <> "a"
+ , "/"
+ , "./r/"
+ , "(" <> strong "l" <> ")"
+ , emph "e" <> "!"
+ , emph "b" <> "."
+ ])
+
+ , "Quotes are allowed border chars" =:
+ "/'yep/ *sure\"*" =?>
+ para (emph "'yep" <> space <> strong "sure\"")
+
+ , "Spaces are forbidden border chars" =:
+ "/nada /" =?>
+ para "/nada /"
+
+ , "Markup should work properly after a blank line" =:
+ T.unlines ["foo", "", "/bar/"] =?>
+ para (text "foo") <>
+ para (emph $ text "bar")
+
+ , "Inline math must stay within three lines" =:
+ T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
+ para (math "a\nb\nc" <> softbreak <>
+ "$d" <> softbreak <> "e" <> softbreak <>
+ "f" <> softbreak <> "g$")
+
+ , "Single-character math" =:
+ "$a$ $b$! $c$?" =?>
+ para (spcSep [ math "a"
+ , "$b$!"
+ , math "c" <> "?"
+ ])
+
+ , "Markup may not span more than two lines" =:
+ "/this *is +totally\nnice+ not*\nemph/" =?>
+ para ("/this" <> space <>
+ strong ("is" <> space <>
+ strikeout ("totally" <>
+ softbreak <> "nice") <>
+ space <> "not") <>
+ softbreak <> "emph/")
+
+ , "Sub- and superscript expressions" =:
+ T.unlines [ "a_(a(b)(c)d)"
+ , "e^(f(g)h)"
+ , "i_(jk)l)"
+ , "m^()n"
+ , "o_{p{q{}r}}"
+ , "s^{t{u}v}"
+ , "w_{xy}z}"
+ , "1^{}2"
+ , "3_{{}}"
+ , "4^(a(*b(c*)d))"
+ ] =?>
+ para (mconcat $ intersperse softbreak
+ [ "a" <> subscript "(a(b)(c)d)"
+ , "e" <> superscript "(f(g)h)"
+ , "i" <> subscript "(jk)" <> "l)"
+ , "m" <> superscript "()" <> "n"
+ , "o" <> subscript "p{q{}r}"
+ , "s" <> superscript "t{u}v"
+ , "w" <> subscript "xy" <> "z}"
+ , "1" <> superscript "" <> "2"
+ , "3" <> subscript "{}"
+ , "4" <> superscript ("(a(" <> strong "b(c" <> ")d))")
+ ])
+ , "Verbatim text can contain equal signes (=)" =:
+ "=is_subst = True=" =?>
+ para (code "is_subst = True")
+
+ , testGroup "Images"
+ [ "Image" =:
+ "[[./sunset.jpg]]" =?>
+ para (image "./sunset.jpg" "" "")
+
+ , "Image with explicit file: prefix" =:
+ "[[file:sunrise.jpg]]" =?>
+ para (image "sunrise.jpg" "" "")
+
+ , "Multiple images within a paragraph" =:
+ T.unlines [ "[[file:sunrise.jpg]]"
+ , "[[file:sunset.jpg]]"
+ ] =?>
+ para ((image "sunrise.jpg" "" "")
+ <> softbreak
+ <> (image "sunset.jpg" "" ""))
+
+ , "Image with html attributes" =:
+ T.unlines [ "#+ATTR_HTML: :width 50%"
+ , "[[file:guinea-pig.gif]]"
+ ] =?>
+ para (imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
+ ]
+
+ , "Explicit link" =:
+ "[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?>
+ para (link "http://zeitlens.com/" ""
+ ("pseudo-random" <> space <> emph "nonsense"))
+
+ , "Self-link" =:
+ "[[http://zeitlens.com/]]" =?>
+ para (link "http://zeitlens.com/" "" "http://zeitlens.com/")
+
+ , "Absolute file link" =:
+ "[[/url][hi]]" =?>
+ para (link "file:///url" "" "hi")
+
+ , "Link to file in parent directory" =:
+ "[[../file.txt][moin]]" =?>
+ para (link "../file.txt" "" "moin")
+
+ , "Empty link (for gitit interop)" =:
+ "[[][New Link]]" =?>
+ para (link "" "" "New Link")
+
+ , "Image link" =:
+ "[[sunset.png][file:dusk.svg]]" =?>
+ para (link "sunset.png" "" (image "dusk.svg" "" ""))
+
+ , "Image link with non-image target" =:
+ "[[http://example.com][./logo.png]]" =?>
+ para (link "http://example.com" "" (image "./logo.png" "" ""))
+
+ , "Plain link" =:
+ "Posts on http://zeitlens.com/ can be funny at times." =?>
+ para (spcSep [ "Posts", "on"
+ , link "http://zeitlens.com/" "" "http://zeitlens.com/"
+ , "can", "be", "funny", "at", "times."
+ ])
+
+ , "Angle link" =:
+ "Look at <http://moltkeplatz.de> for fnords." =?>
+ para (spcSep [ "Look", "at"
+ , link "http://moltkeplatz.de" "" "http://moltkeplatz.de"
+ , "for", "fnords."
+ ])
+
+ , "Absolute file link" =:
+ "[[file:///etc/passwd][passwd]]" =?>
+ para (link "file:///etc/passwd" "" "passwd")
+
+ , "File link" =:
+ "[[file:target][title]]" =?>
+ para (link "target" "" "title")
+
+ , "Anchor" =:
+ "<<anchor>> Link here later." =?>
+ para (spanWith ("anchor", [], []) mempty <>
+ "Link" <> space <> "here" <> space <> "later.")
+
+ , "Inline code block" =:
+ "src_emacs-lisp{(message \"Hello\")}" =?>
+ para (codeWith ( ""
+ , [ "commonlisp" ]
+ , [ ("org-language", "emacs-lisp") ])
+ "(message \"Hello\")")
+
+ , "Inline code block with arguments" =:
+ "src_sh[:export both :results output]{echo 'Hello, World'}" =?>
+ para (codeWith ( ""
+ , [ "bash" ]
+ , [ ("org-language", "sh")
+ , ("export", "both")
+ , ("results", "output")
+ ]
+ )
+ "echo 'Hello, World'")
+
+ , "Inline code block with toggle" =:
+ "src_sh[:toggle]{echo $HOME}" =?>
+ para (codeWith ( ""
+ , [ "bash" ]
+ , [ ("org-language", "sh")
+ , ("toggle", "yes")
+ ]
+ )
+ "echo $HOME")
+
+ , "Inline LaTeX symbol" =:
+ "\\dots" =?>
+ para "…"
+
+ , "Inline LaTeX command" =:
+ "\\textit{Emphasised}" =?>
+ para (emph "Emphasised")
+
+ , "Inline LaTeX command with spaces" =:
+ "\\emph{Emphasis mine}" =?>
+ para (emph "Emphasis mine")
+
+ , "Inline LaTeX math symbol" =:
+ "\\tau" =?>
+ para (emph "τ")
+
+ , "Unknown inline LaTeX command" =:
+ "\\notacommand{foo}" =?>
+ para (rawInline "latex" "\\notacommand{foo}")
+
+ , "Export snippet" =:
+ "@@html:<kbd>M-x org-agenda</kbd>@@" =?>
+ para (rawInline "html" "<kbd>M-x org-agenda</kbd>")
+
+ , "MathML symbol in LaTeX-style" =:
+ "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
+ para "There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ')."
+
+ , "MathML symbol in LaTeX-style, including braces" =:
+ "\\Aacute{}stor" =?>
+ para "Ástor"
+
+ , "MathML copy sign" =:
+ "\\copy" =?>
+ para "©"
+
+ , "MathML symbols, space separated" =:
+ "\\ForAll \\Auml" =?>
+ para "∀ Ä"
+
+ , "Macro" =:
+ T.unlines [ "#+MACRO: HELLO /Hello, $1/"
+ , "{{{HELLO(World)}}}"
+ ] =?>
+ para (emph "Hello, World")
+
+ , "Macro repeting its argument" =:
+ T.unlines [ "#+MACRO: HELLO $1$1"
+ , "{{{HELLO(moin)}}}"
+ ] =?>
+ para "moinmoin"
+
+ , "Macro called with too few arguments" =:
+ T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar"
+ , "{{{HELLO()}}}"
+ ] =?>
+ para "Foo Bar"
+
+ , testGroup "Citations" Citation.tests
+ , testGroup "Footnotes" Note.tests
+ , testGroup "Smart punctuation" Smart.tests
+ ]
diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs
new file mode 100644
index 000000000..d7e38a6b0
--- /dev/null
+++ b/test/Tests/Readers/Org/Inline/Citation.hs
@@ -0,0 +1,179 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Inline.Citation (tests) where
+
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:))
+import Text.Pandoc.Builder
+
+tests :: [TestTree]
+tests =
+ [ testGroup "Markdown-style citations"
+ [ "Citation" =:
+ "[@nonexistent]" =?>
+ let citation = Citation
+ { citationId = "nonexistent"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0}
+ in (para $ cite [citation] "[@nonexistent]")
+
+ , "Citation containing text" =:
+ "[see @item1 p. 34-35]" =?>
+ let citation = Citation
+ { citationId = "item1"
+ , citationPrefix = [Str "see"]
+ , citationSuffix = [Space ,Str "p.",Space,Str "34-35"]
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0}
+ in (para $ cite [citation] "[see @item1 p. 34-35]")
+ ]
+
+ , testGroup "org-ref citations"
+ [ "simple citation" =:
+ "cite:pandoc" =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc")
+
+ , "simple citation with underscores" =:
+ "cite:pandoc_org_ref" =?>
+ let citation = Citation
+ { citationId = "pandoc_org_ref"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc_org_ref")
+
+ , "simple citation succeeded by comma" =:
+ "cite:pandoc," =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc" <> str ",")
+
+ , "simple citation succeeded by dot" =:
+ "cite:pandoc." =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc" <> str ".")
+
+ , "simple citation succeeded by colon" =:
+ "cite:pandoc:" =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc" <> str ":")
+
+ , "simple citep citation" =:
+ "citep:pandoc" =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "citep:pandoc")
+
+ , "extended citation" =:
+ "[[citep:Dominik201408][See page 20::, for example]]" =?>
+ let citation = Citation
+ { citationId = "Dominik201408"
+ , citationPrefix = toList "See page 20"
+ , citationSuffix = toList ", for example"
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "[[citep:Dominik201408][See page 20::, for example]]")
+ ]
+
+ , testGroup "Berkeley-style citations" $
+ let pandocCite = Citation
+ { citationId = "Pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ pandocInText = pandocCite { citationMode = AuthorInText }
+ dominikCite = Citation
+ { citationId = "Dominik201408"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ dominikInText = dominikCite { citationMode = AuthorInText }
+ in
+ [ "Berkeley-style in-text citation" =:
+ "See @Dominik201408." =?>
+ para ("See "
+ <> cite [dominikInText] "@Dominik201408"
+ <> ".")
+
+ , "Berkeley-style parenthetical citation list" =:
+ "[(cite): see; @Dominik201408;also @Pandoc; and others]" =?>
+ let pandocCite' = pandocCite {
+ citationPrefix = toList "also"
+ , citationSuffix = toList "and others"
+ }
+ dominikCite' = dominikCite {
+ citationPrefix = toList "see"
+ }
+ in (para $ cite [dominikCite', pandocCite'] "")
+
+ , "Berkeley-style plain citation list" =:
+ "[cite: See; @Dominik201408; and @Pandoc; and others]" =?>
+ let pandocCite' = pandocInText { citationPrefix = toList "and" }
+ in (para $ "See "
+ <> cite [dominikInText] ""
+ <> "," <> space
+ <> cite [pandocCite'] ""
+ <> "," <> space <> "and others")
+ ]
+
+ , "LaTeX citation" =:
+ "\\cite{Coffee}" =?>
+ let citation = Citation
+ { citationId = "Coffee"
+ , citationPrefix = []
+ , citationSuffix = []
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0}
+ in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
+
+ ]
diff --git a/test/Tests/Readers/Org/Inline/Note.hs b/test/Tests/Readers/Org/Inline/Note.hs
new file mode 100644
index 000000000..9eb1d02d6
--- /dev/null
+++ b/test/Tests/Readers/Org/Inline/Note.hs
@@ -0,0 +1,86 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Inline.Note (tests) where
+
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:))
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "Footnote" =:
+ T.unlines [ "A footnote[1]"
+ , ""
+ , "[1] First paragraph"
+ , ""
+ , "second paragraph"
+ ] =?>
+ para (mconcat
+ [ "A", space, "footnote"
+ , note $ mconcat [ para ("First" <> space <> "paragraph")
+ , para ("second" <> space <> "paragraph")
+ ]
+ ])
+
+ , "Two footnotes" =:
+ T.unlines [ "Footnotes[fn:1][fn:2]"
+ , ""
+ , "[fn:1] First note."
+ , ""
+ , "[fn:2] Second note."
+ ] =?>
+ para (mconcat
+ [ "Footnotes"
+ , note $ para ("First" <> space <> "note.")
+ , note $ para ("Second" <> space <> "note.")
+ ])
+
+ , "Emphasized text before footnote" =:
+ T.unlines [ "/text/[fn:1]"
+ , ""
+ , "[fn:1] unicorn"
+ ] =?>
+ para (mconcat
+ [ emph "text"
+ , note . para $ "unicorn"
+ ])
+
+ , "Footnote that starts with emphasized text" =:
+ T.unlines [ "text[fn:1]"
+ , ""
+ , "[fn:1] /emphasized/"
+ ] =?>
+ para (mconcat
+ [ "text"
+ , note . para $ emph "emphasized"
+ ])
+
+ , "Footnote followed by header" =:
+ T.unlines [ "Another note[fn:yay]"
+ , ""
+ , "[fn:yay] This is great!"
+ , ""
+ , "** Headline"
+ ] =?>
+ mconcat
+ [ para (mconcat
+ [ "Another", space, "note"
+ , note $ para ("This" <> space <> "is" <> space <> "great!")
+ ])
+ , headerWith ("headline", [], []) 2 "Headline"
+ ]
+
+ , "Footnote followed by two blank lines" =:
+ T.unlines [ "footnote[fn:blanklines]"
+ , ""
+ , "[fn:blanklines] followed by blank lines"
+ , ""
+ , ""
+ , "next"
+ ] =?>
+ mconcat
+ [ para ("footnote" <> note (para "followed by blank lines"))
+ , para "next"
+ ]
+ ]
diff --git a/test/Tests/Readers/Org/Inline/Smart.hs b/test/Tests/Readers/Org/Inline/Smart.hs
new file mode 100644
index 000000000..77f10699d
--- /dev/null
+++ b/test/Tests/Readers/Org/Inline/Smart.hs
@@ -0,0 +1,46 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Inline.Smart (tests) where
+
+import Data.Text (Text)
+import Test.Tasty (TestTree)
+import Tests.Helpers ((=?>), purely, test)
+import Text.Pandoc (ReaderOptions (readerExtensions),
+ Extension (Ext_smart), def, enableExtension,
+ getDefaultExtensions, readOrg)
+import Text.Pandoc.Builder
+
+orgSmart :: Text -> Pandoc
+orgSmart = purely $
+ let extensionsSmart = enableExtension Ext_smart (getDefaultExtensions "org")
+ in readOrg def{ readerExtensions = extensionsSmart }
+
+tests :: [TestTree]
+tests =
+ [ test orgSmart "quote before ellipses"
+ ("'...hi'"
+ =?> para (singleQuoted "…hi"))
+
+ , test orgSmart "apostrophe before emph"
+ ("D'oh! A l'/aide/!"
+ =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
+
+ , test orgSmart "apostrophe in French"
+ ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
+ =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+
+ , test orgSmart "Quotes cannot occur at the end of emphasized text"
+ ("/say \"yes\"/" =?>
+ para ("/say" <> space <> doubleQuoted "yes" <> "/"))
+
+ , test orgSmart "Dashes are allowed at the borders of emphasis'"
+ ("/foo---/" =?>
+ para (emph "foo—"))
+
+ , test orgSmart "Single quotes can be followed by emphasized text"
+ ("Singles on the '/meat market/'" =?>
+ para ("Singles on the " <> singleQuoted (emph "meat market")))
+
+ , test orgSmart "Double quotes can be followed by emphasized text"
+ ("Double income, no kids: \"/DINK/\"" =?>
+ para ("Double income, no kids: " <> doubleQuoted (emph "DINK")))
+ ]
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
new file mode 100644
index 000000000..6bd1b02e7
--- /dev/null
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -0,0 +1,191 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Org.Meta (tests) where
+
+import Test.Tasty (TestTree, testGroup)
+import Tests.Helpers ((=?>))
+import Tests.Readers.Org.Shared ((=:), spcSep)
+import Text.Pandoc
+import Text.Pandoc.Builder
+import qualified Data.Text as T
+
+tests :: [TestTree]
+tests =
+ [ "Comment" =:
+ "# Nothing to see here" =?>
+ (mempty::Blocks)
+
+ , "Not a comment" =:
+ "#-tag" =?>
+ para "#-tag"
+
+ , "Comment surrounded by Text" =:
+ T.unlines [ "Before"
+ , "# Comment"
+ , "After"
+ ] =?>
+ mconcat [ para "Before"
+ , para "After"
+ ]
+
+ , "Title" =:
+ "#+TITLE: Hello, World" =?>
+ let titleInline = toList $ "Hello," <> space <> "World"
+ meta = setMeta "title" (MetaInlines titleInline) nullMeta
+ in Pandoc meta mempty
+
+ , "Author" =:
+ "#+author: John /Emacs-Fanboy/ Doe" =?>
+ let author = toList . spcSep $ [ "John", emph "Emacs-Fanboy", "Doe" ]
+ meta = setMeta "author" (MetaList [MetaInlines author]) nullMeta
+ in Pandoc meta mempty
+
+ , "Multiple authors" =:
+ "#+author: James Dewey Watson, Francis Harry Compton Crick " =?>
+ let watson = MetaInlines $ toList "James Dewey Watson"
+ crick = MetaInlines $ toList "Francis Harry Compton Crick"
+ meta = setMeta "author" (MetaList [watson, crick]) nullMeta
+ in Pandoc meta mempty
+
+ , "Date" =:
+ "#+Date: Feb. *28*, 2014" =?>
+ let date = toList . spcSep $ [ "Feb.", strong "28" <> ",", "2014" ]
+ meta = setMeta "date" (MetaInlines date) nullMeta
+ in Pandoc meta mempty
+
+ , "Description" =:
+ "#+DESCRIPTION: Explanatory text" =?>
+ let description = "Explanatory text"
+ meta = setMeta "description" (MetaString description) nullMeta
+ in Pandoc meta mempty
+
+ , "Properties drawer" =:
+ T.unlines [ " :PROPERTIES:"
+ , " :setting: foo"
+ , " :END:"
+ ] =?>
+ (mempty::Blocks)
+
+ , "LaTeX_headers options are translated to header-includes" =:
+ "#+LaTeX_header: \\usepackage{tikz}" =?>
+ let latexInlines = rawInline "latex" "\\usepackage{tikz}"
+ inclList = MetaList [MetaInlines (toList latexInlines)]
+ meta = setMeta "header-includes" inclList nullMeta
+ in Pandoc meta mempty
+
+ , "LaTeX_class option is translated to documentclass" =:
+ "#+LATEX_CLASS: article" =?>
+ let meta = setMeta "documentclass" (MetaString "article") nullMeta
+ in Pandoc meta mempty
+
+ , "LaTeX_class_options is translated to classoption" =:
+ "#+LATEX_CLASS_OPTIONS: [a4paper]" =?>
+ let meta = setMeta "classoption" (MetaString "a4paper") nullMeta
+ in Pandoc meta mempty
+
+ , "LaTeX_class_options is translated to classoption" =:
+ "#+html_head: <meta/>" =?>
+ let html = rawInline "html" "<meta/>"
+ inclList = MetaList [MetaInlines (toList html)]
+ meta = setMeta "header-includes" inclList nullMeta
+ in Pandoc meta mempty
+
+ , "later meta definitions take precedence" =:
+ T.unlines [ "#+AUTHOR: this will not be used"
+ , "#+author: Max"
+ ] =?>
+ let author = MetaInlines [Str "Max"]
+ meta = setMeta "author" (MetaList [author]) nullMeta
+ in Pandoc meta mempty
+
+ , "Logbook drawer" =:
+ T.unlines [ " :LogBook:"
+ , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]"
+ , " :END:"
+ ] =?>
+ (mempty::Blocks)
+
+ , "Drawer surrounded by text" =:
+ T.unlines [ "Before"
+ , ":PROPERTIES:"
+ , ":END:"
+ , "After"
+ ] =?>
+ para "Before" <> para "After"
+
+ , "Drawer markers must be the only text in the line" =:
+ T.unlines [ " :LOGBOOK: foo"
+ , " :END: bar"
+ ] =?>
+ para (":LOGBOOK: foo" <> softbreak <> ":END: bar")
+
+ , "Drawers can be arbitrary" =:
+ T.unlines [ ":FOO:"
+ , "/bar/"
+ , ":END:"
+ ] =?>
+ divWith (mempty, ["FOO", "drawer"], mempty) (para $ emph "bar")
+
+ , "Anchor reference" =:
+ T.unlines [ "<<link-here>> Target."
+ , ""
+ , "[[link-here][See here!]]"
+ ] =?>
+ (para (spanWith ("link-here", [], []) mempty <> "Target.") <>
+ para (link "#link-here" "" ("See" <> space <> "here!")))
+
+ , "Search links are read as emph" =:
+ "[[Wally][Where's Wally?]]" =?>
+ para (emph $ "Where's" <> space <> "Wally?")
+
+ , "Link to nonexistent anchor" =:
+ T.unlines [ "<<link-here>> Target."
+ , ""
+ , "[[link$here][See here!]]"
+ ] =?>
+ (para (spanWith ("link-here", [], []) mempty <> "Target.") <>
+ para (emph ("See" <> space <> "here!")))
+
+ , "Link abbreviation" =:
+ T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
+ , "[[wp:Org_mode][Wikipedia on Org-mode]]"
+ ] =?>
+ para (link "https://en.wikipedia.org/wiki/Org_mode" ""
+ ("Wikipedia" <> space <> "on" <> space <> "Org-mode"))
+
+ , "Link abbreviation, defined after first use" =:
+ T.unlines [ "[[zl:non-sense][Non-sense articles]]"
+ , "#+LINK: zl http://zeitlens.com/tags/%s.html"
+ ] =?>
+ para (link "http://zeitlens.com/tags/non-sense.html" ""
+ ("Non-sense" <> space <> "articles"))
+
+ , "Link abbreviation, URL encoded arguments" =:
+ T.unlines [ "#+link: expl http://example.com/%h/foo"
+ , "[[expl:Hello, World!][Moin!]]"
+ ] =?>
+ para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!")
+
+ , "Link abbreviation, append arguments" =:
+ T.unlines [ "#+link: expl http://example.com/"
+ , "[[expl:foo][bar]]"
+ ] =?>
+ para (link "http://example.com/foo" "" "bar")
+
+ , testGroup "emphasis config"
+ [ "Changing pre and post chars for emphasis" =:
+ T.unlines [ "#+pandoc-emphasis-pre: \"[)\""
+ , "#+pandoc-emphasis-post: \"]\\n\""
+ , "([/emph/])*foo*"
+ ] =?>
+ para ("([" <> emph "emph" <> "])" <> strong "foo")
+
+ , "setting an invalid value restores the default" =:
+ T.unlines [ "#+pandoc-emphasis-pre: \"[\""
+ , "#+pandoc-emphasis-post: \"]\""
+ , "#+pandoc-emphasis-pre:"
+ , "#+pandoc-emphasis-post:"
+ , "[/noemph/]"
+ ] =?>
+ para ("[/noemph/]")
+ ]
+ ]
diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs
new file mode 100644
index 000000000..5e8f6dd54
--- /dev/null
+++ b/test/Tests/Readers/Org/Shared.hs
@@ -0,0 +1,29 @@
+module Tests.Readers.Org.Shared
+ ( (=:)
+ , org
+ , spcSep
+ , tagSpan
+ ) where
+
+import Data.List (intersperse)
+import Data.Text (Text)
+import Tests.Helpers (ToString, purely, test)
+import Test.Tasty (TestTree)
+import Text.Pandoc (Pandoc, ReaderOptions (readerExtensions),
+ def, getDefaultExtensions, readOrg)
+import Text.Pandoc.Builder (Inlines, smallcaps, space, spanWith, str)
+
+org :: Text -> Pandoc
+org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test org
+
+spcSep :: [Inlines] -> Inlines
+spcSep = mconcat . intersperse space
+
+-- | Create a span for the given tag.
+tagSpan :: String -> Inlines
+tagSpan t = spanWith ("", ["tag"], [("tag-name", t)]) . smallcaps $ str t
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
new file mode 100644
index 000000000..3753fbf12
--- /dev/null
+++ b/test/Tests/Readers/RST.hs
@@ -0,0 +1,189 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module Tests.Readers.RST (tests) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+rst :: Text -> Pandoc
+rst = purely $ readRST def{ readerStandalone = True }
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test rst
+
+tests :: [TestTree]
+tests = [ "line block with blank line" =:
+ "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ]
+ , testGroup "field list"
+ [ "general" =: T.unlines
+ [ "para"
+ , ""
+ , ":Hostname: media08"
+ , ":IP address: 10.0.0.19"
+ , ":Size: 3ru"
+ , ":Version: 1"
+ , ":Indentation: Since the field marker may be quite long, the second"
+ , " and subsequent lines of the field body do not have to line up"
+ , " with the first line, but they must be indented relative to the"
+ , " field name marker, and they must line up with each other."
+ , ":Parameter i: integer"
+ , ":Final: item"
+ , " on two lines" ]
+ =?>
+ doc (para "para" <>
+ definitionList [ (str "Hostname", [para "media08"])
+ , (text "IP address", [para "10.0.0.19"])
+ , (str "Size", [para "3ru"])
+ , (str "Version", [para "1"])
+ , (str "Indentation", [para "Since the field marker may be quite long, the second\nand subsequent lines of the field body do not have to line up\nwith the first line, but they must be indented relative to the\nfield name marker, and they must line up with each other."])
+ , (text "Parameter i", [para "integer"])
+ , (str "Final", [para "item\non two lines"])
+ ])
+ , "metadata" =: T.unlines
+ [ "====="
+ , "Title"
+ , "====="
+ , "--------"
+ , "Subtitle"
+ , "--------"
+ , ""
+ , ":Version: 1"
+ ]
+ =?>
+ setMeta "version" (para "1") (setMeta "title" ("Title" :: Inlines)
+ $ setMeta "subtitle" ("Subtitle" :: Inlines)
+ $ doc mempty)
+ , "with inline markup" =: T.unlines
+ [ ":*Date*: today"
+ , ""
+ , ".."
+ , ""
+ , ":*one*: emphasis"
+ , ":two_: reference"
+ , ":`three`_: another one"
+ , ":``four``: literal"
+ , ""
+ , ".. _two: http://example.com"
+ , ".. _three: http://example.org"
+ ]
+ =?>
+ setMeta "date" (str "today") (doc
+ $ definitionList [ (emph "one", [para "emphasis"])
+ , (link "http://example.com" "" "two", [para "reference"])
+ , (link "http://example.org" "" "three", [para "another one"])
+ , (code "four", [para "literal"])
+ ])
+ ]
+ , "URLs with following punctuation" =:
+ ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" <>
+ "http://foo.bar/baz_(bam) (http://foo.bar)") =?>
+ para (link "http://google.com" "" "http://google.com" <> ", " <>
+ link "http://yahoo.com" "" "http://yahoo.com" <> "; " <>
+ link "http://foo.bar.baz" "" "http://foo.bar.baz" <> ". " <>
+ softbreak <>
+ link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)"
+ <> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")")
+ , "Reference names with special characters" =:
+ ("A-1-B_2_C:3:D+4+E.5.F_\n\n" <>
+ ".. _A-1-B_2_C:3:D+4+E.5.F: https://example.com\n") =?>
+ para (link "https://example.com" "" "A-1-B_2_C:3:D+4+E.5.F")
+ , "Code directive with class and number-lines" =: T.unlines
+ [ ".. code::python"
+ , " :number-lines: 34"
+ , " :class: class1 class2 class3"
+ , ""
+ , " def func(x):"
+ , " return y"
+ ] =?>
+ doc (codeBlockWith
+ ( ""
+ , ["sourceCode", "python", "numberLines", "class1", "class2", "class3"]
+ , [ ("startFrom", "34") ]
+ )
+ "def func(x):\n return y")
+ , "Code directive with number-lines, no line specified" =: T.unlines
+ [ ".. code::python"
+ , " :number-lines: "
+ , ""
+ , " def func(x):"
+ , " return y"
+ ] =?>
+ doc (codeBlockWith
+ ( ""
+ , ["sourceCode", "python", "numberLines"]
+ , [ ("startFrom", "") ]
+ )
+ "def func(x):\n return y")
+ , testGroup "literal / line / code blocks"
+ [ "indented literal block" =: T.unlines
+ [ "::"
+ , ""
+ , " block quotes"
+ , ""
+ , " can go on for many lines"
+ , "but must stop here"]
+ =?>
+ doc (
+ codeBlock "block quotes\n\ncan go on for many lines" <>
+ para "but must stop here")
+ , "line block with 3 lines" =: "| a\n| b\n| c"
+ =?> lineBlock ["a", "b", "c"]
+ , "line blocks with blank lines" =: T.unlines
+ [ "|"
+ , ""
+ , "|"
+ , "| a"
+ , "| b"
+ , "|"
+ , ""
+ , "|"
+ ] =?>
+ lineBlock [""] <>
+ lineBlock ["", "a", "b", ""] <>
+ lineBlock [""]
+ , "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph"
+ =?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph"
+ , "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph"
+ =?> codeBlock "| quoted\n| block" <> para "Ordinary paragraph"
+ , "class directive with single paragraph" =: ".. class:: special\n\nThis is a \"special\" paragraph."
+ =?> divWith ("", ["special"], []) (para "This is a \"special\" paragraph.")
+ , "class directive with two paragraphs" =: ".. class:: exceptional remarkable\n\n First paragraph.\n\n Second paragraph."
+ =?> divWith ("", ["exceptional", "remarkable"], []) (para "First paragraph." <> para "Second paragraph.")
+ , "class directive around literal block" =: ".. class:: classy\n\n::\n\n a\n b"
+ =?> divWith ("", ["classy"], []) (codeBlock "a\nb")]
+ , testGroup "interpreted text roles"
+ [ "literal role prefix" =: ":literal:`a`" =?> para (code "a")
+ , "literal role postfix" =: "`a`:literal:" =?> para (code "a")
+ , "literal text" =: "``text``" =?> para (code "text")
+ , "code role" =: ":code:`a`" =?> para (codeWith ("", ["sourceCode"], []) "a")
+ , "inherited code role" =: ".. role:: codeLike(code)\n\n:codeLike:`a`"
+ =?> para (codeWith ("", ["codeLike", "sourceCode"], []) "a")
+ , "custom code role with language field"
+ =: ".. role:: lhs(code)\n :language: haskell\n\n:lhs:`a`"
+ =?> para (codeWith ("", ["lhs", "haskell","sourceCode"], []) "a")
+ , "custom role with unspecified parent role"
+ =: ".. role:: classy\n\n:classy:`text`"
+ =?> para (spanWith ("", ["classy"], []) "text")
+ , "role with recursive inheritance"
+ =: ".. role:: haskell(code)\n.. role:: lhs(haskell)\n\n:lhs:`text`"
+ =?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text")
+ , "unknown role" =: ":unknown:`text`" =?>
+ para (spanWith ("",[],[("role","unknown")]) (str "text"))
+ ]
+ , testGroup "footnotes"
+ [ "remove space before note" =: T.unlines
+ [ "foo [1]_"
+ , ""
+ , ".. [1]"
+ , " bar"
+ ] =?>
+ para ("foo" <> (note $ para "bar"))
+ ]
+ ]
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
new file mode 100644
index 000000000..435d983a1
--- /dev/null
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -0,0 +1,437 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Txt2Tags (tests) where
+
+import Data.List (intersperse)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+import Text.Pandoc.Shared (underlineSpan)
+
+t2t :: Text -> Pandoc
+-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
+t2t = purely $ \s -> do
+ setInputFiles ["in"]
+ setOutputFile (Just "out")
+ readTxt2Tags def s
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test t2t
+
+spcSep :: [Inlines] -> Inlines
+spcSep = mconcat . intersperse space
+
+simpleTable' :: Int
+ -> [Blocks]
+ -> [[Blocks]]
+ -> Blocks
+simpleTable' n = table "" (replicate n (AlignCenter, 0.0))
+
+tests :: [TestTree]
+tests =
+ [ testGroup "Inlines"
+ [ "Plain String" =:
+ "Hello, World" =?>
+ para (spcSep [ "Hello,", "World" ])
+
+ , "Emphasis" =:
+ "//Planet Punk//" =?>
+ para (emph . spcSep $ ["Planet", "Punk"])
+
+ , "Strong" =:
+ "**Cider**" =?>
+ para (strong "Cider")
+
+ , "Strong Emphasis" =:
+ "//**strength**//" =?>
+ para (emph . strong $ "strength")
+
+ , "Strikeout" =:
+ "--Kill Bill--" =?>
+ para (strikeout . spcSep $ [ "Kill", "Bill" ])
+
+ , "Verbatim" =:
+ "``Robot.rock()``" =?>
+ para (code "Robot.rock()")
+
+ , "Symbol" =:
+ "A * symbol" =?>
+ para (str "A" <> space <> str "*" <> space <> "symbol")
+
+ , "No empty markup" =:
+ "//// **** ____ ---- ```` \"\"\"\" ''''" =?>
+ para (spcSep [ "////", "****", "____", "----", "````", "\"\"\"\"", "''''" ])
+
+ , "Inline markup is greedy" =:
+ "***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?>
+ para (spcSep [strong "*", emph "/", underlineSpan "_"
+ , strikeout "-", code "`", text "\""
+ , rawInline "html" "'"])
+ , "Markup must be greedy" =:
+ "********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?>
+ para (spcSep [strong "******", emph "//////", underlineSpan "______"
+ , strikeout "------", code "``````", text "\"\"\"\"\"\""
+ , rawInline "html" "''''''"])
+ , "Inlines must be glued" =:
+ "** a** **a ** ** a **" =?>
+ para (text "** a** **a ** ** a **")
+
+ , "Macros: Date" =:
+ "%%date" =?>
+ para "1970-01-01"
+ , "Macros: Mod Time" =:
+ "%%mtime" =?>
+ para (str "")
+ , "Macros: Infile" =:
+ "%%infile" =?>
+ para "in"
+ , "Macros: Outfile" =:
+ "%%outfile" =?>
+ para "out"
+ , "Autolink" =:
+ "http://www.google.com" =?>
+ para (link "http://www.google.com" "" (str "http://www.google.com"))
+ , "JPEG Image" =:
+ "[image.jpg]" =?>
+ para (image "image.jpg" "" mempty)
+ , "PNG Image" =:
+ "[image.png]" =?>
+ para (image "image.png" "" mempty)
+
+ , "Link" =:
+ "[title http://google.com]" =?>
+ para (link "http://google.com" "" (str "title"))
+
+ , "Image link" =:
+ "[[image.jpg] abc]" =?>
+ para (link "abc" "" (image "image.jpg" "" mempty))
+ , "Invalid link: No trailing space" =:
+ "[title invalid ]" =?>
+ para (text "[title invalid ]")
+
+
+ ]
+
+ , testGroup "Basic Blocks"
+ ["Paragraph, lines grouped together" =:
+ "A paragraph\n A blank line ends the \n current paragraph\n"
+ =?> para "A paragraph\n A blank line ends the\n current paragraph"
+ , "Paragraph, ignore leading and trailing spaces" =:
+ " Leading and trailing spaces are ignored. \n" =?>
+ para "Leading and trailing spaces are ignored."
+ , "Comment line in paragraph" =:
+ "A comment line can be placed inside a paragraph.\n% this comment will be ignored \nIt will not affect it.\n"
+ =?> para "A comment line can be placed inside a paragraph.\nIt will not affect it."
+ , "Paragraph" =:
+ "Paragraph\n" =?>
+ para "Paragraph"
+
+ , "First Level Header" =:
+ "+ Headline +\n" =?>
+ header 1 "Headline"
+
+ , "Third Level Header" =:
+ "=== Third Level Headline ===\n" =?>
+ header 3 ("Third" <> space <>
+ "Level" <> space <>
+ "Headline")
+
+ , "Header with label" =:
+ "= header =[label]" =?>
+ headerWith ("label", [], []) 1 ("header")
+
+ , "Invalid header, mismatched delimiters" =:
+ "== header =" =?>
+ para (text "== header =")
+
+ , "Invalid header, spaces in label" =:
+ "== header ==[ haha ]" =?>
+ para (text "== header ==[ haha ]")
+
+ , "Invalid header, invalid label character" =:
+ "== header ==[lab/el]" =?>
+ para (text "== header ==[lab/el]")
+ , "Headers not preceded by a blank line" =:
+ T.unlines [ "++ eat dinner ++"
+ , "Spaghetti and meatballs tonight."
+ , "== walk dog =="
+ ] =?>
+ mconcat [ header 2 ("eat" <> space <> "dinner")
+ , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ]
+ , header 2 ("walk" <> space <> "dog")
+ ]
+
+ , "Paragraph starting with an equals" =:
+ "=five" =?>
+ para "=five"
+
+ , "Paragraph containing asterisk at beginning of line" =:
+ T.unlines [ "lucky"
+ , "*star"
+ ] =?>
+ para ("lucky" <> softbreak <> "*star")
+
+ , "Horizontal Rule" =:
+ T.unlines [ "before"
+ , T.replicate 20 "-"
+ , T.replicate 20 "="
+ , T.replicate 20 "_"
+ , "after"
+ ] =?>
+ mconcat [ para "before"
+ , horizontalRule
+ , horizontalRule
+ , horizontalRule
+ , para "after"
+ ]
+
+ , "Comment Block" =:
+ T.unlines [ "%%%"
+ , "stuff"
+ , "bla"
+ , "%%%"] =?>
+ (mempty::Blocks)
+
+
+ ]
+
+ , testGroup "Lists"
+ [ "Simple Bullet Lists" =:
+ ("- Item1\n" <>
+ "- Item2\n") =?>
+ bulletList [ plain "Item1"
+ , plain "Item2"
+ ]
+
+ , "Indented Bullet Lists" =:
+ (" - Item1\n" <>
+ " - Item2\n") =?>
+ bulletList [ plain "Item1"
+ , plain "Item2"
+ ]
+
+
+
+ , "Nested Bullet Lists" =:
+ ("- Discovery\n" <>
+ " + One More Time\n" <>
+ " + Harder, Better, Faster, Stronger\n" <>
+ "- Homework\n" <>
+ " + Around the World\n"<>
+ "- Human After All\n" <>
+ " + Technologic\n" <>
+ " + Robot Rock\n") =?>
+ bulletList [ mconcat
+ [ plain "Discovery"
+ , orderedList [ plain ("One" <> space <>
+ "More" <> space <>
+ "Time")
+ , plain ("Harder," <> space <>
+ "Better," <> space <>
+ "Faster," <> space <>
+ "Stronger")
+ ]
+ ]
+ , mconcat
+ [ plain "Homework"
+ , orderedList [ plain ("Around" <> space <>
+ "the" <> space <>
+ "World")
+ ]
+ ]
+ , mconcat
+ [ plain ("Human" <> space <> "After" <> space <> "All")
+ , orderedList [ plain "Technologic"
+ , plain ("Robot" <> space <> "Rock")
+ ]
+ ]
+ ]
+
+ , "Simple Ordered List" =:
+ ("+ Item1\n" <>
+ "+ Item2\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ plain "Item1"
+ , plain "Item2"
+ ]
+ in orderedListWith listStyle listStructure
+
+
+ , "Indented Ordered List" =:
+ (" + Item1\n" <>
+ " + Item2\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ plain "Item1"
+ , plain "Item2"
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Nested Ordered Lists" =:
+ ("+ One\n" <>
+ " + One-One\n" <>
+ " + One-Two\n" <>
+ "+ Two\n" <>
+ " + Two-One\n"<>
+ " + Two-Two\n") =?>
+ let listStyle = (1, DefaultStyle, DefaultDelim)
+ listStructure = [ mconcat
+ [ plain "One"
+ , orderedList [ plain "One-One"
+ , plain "One-Two"
+ ]
+ ]
+ , mconcat
+ [ plain "Two"
+ , orderedList [ plain "Two-One"
+ , plain "Two-Two"
+ ]
+ ]
+ ]
+ in orderedListWith listStyle listStructure
+
+ , "Ordered List in Bullet List" =:
+ ("- Emacs\n" <>
+ " + Org\n") =?>
+ bulletList [ (plain "Emacs") <>
+ (orderedList [ plain "Org"])
+ ]
+
+ , "Bullet List in Ordered List" =:
+ ("+ GNU\n" <>
+ " - Freedom\n") =?>
+ orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ]
+
+ , "Definition List" =:
+ T.unlines [ ": PLL"
+ , " phase-locked loop"
+ , ": TTL"
+ , " transistor-transistor logic"
+ , ": PSK"
+ , " a digital"
+ ] =?>
+ definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ])
+ , ("TTL", [ plain $ "transistor-transistor" <> space <> "logic" ])
+ , ("PSK", [ plain $ "a" <> space <> "digital" ])
+ ]
+
+
+ , "Loose bullet list" =:
+ T.unlines [ "- apple"
+ , ""
+ , "- orange"
+ , ""
+ , "- peach"
+ ] =?>
+ bulletList [ para "apple"
+ , para "orange"
+ , para "peach"
+ ]
+ ]
+
+ , testGroup "Tables"
+ [ "Single cell table" =:
+ "| Test " =?>
+ simpleTable' 1 mempty [[plain "Test"]]
+
+ , "Multi cell table" =:
+ "| One | Two |" =?>
+ simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
+
+ , "Multi line table" =:
+ T.unlines [ "| One |"
+ , "| Two |"
+ , "| Three |"
+ ] =?>
+ simpleTable' 1 mempty
+ [ [ plain "One" ]
+ , [ plain "Two" ]
+ , [ plain "Three" ]
+ ]
+
+ , "Empty table" =:
+ "| |" =?>
+ simpleTable' 1 mempty [[mempty]]
+
+ , "Glider Table" =:
+ T.unlines [ "| 1 | 0 | 0 |"
+ , "| 0 | 1 | 1 |"
+ , "| 1 | 1 | 0 |"
+ ] =?>
+ simpleTable' 3 mempty
+ [ [ plain "1", plain "0", plain "0" ]
+ , [ plain "0", plain "1", plain "1" ]
+ , [ plain "1", plain "1", plain "0" ]
+ ]
+
+
+ , "Table with Header" =:
+ T.unlines [ "|| Species | Status |"
+ , "| cervisiae | domesticated |"
+ , "| paradoxus | wild |"
+ ] =?>
+ simpleTable [ plain "Species", plain "Status" ]
+ [ [ plain "cervisiae", plain "domesticated" ]
+ , [ plain "paradoxus", plain "wild" ]
+ ]
+
+ , "Table alignment determined by spacing" =:
+ T.unlines [ "| Numbers | Text | More |"
+ , "| 1 | One | foo |"
+ , "| 2 | Two | bar |"
+ ] =?>
+ table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
+ []
+ [ [ plain "Numbers", plain "Text", plain "More" ]
+ , [ plain "1" , plain "One" , plain "foo" ]
+ , [ plain "2" , plain "Two" , plain "bar" ]
+ ]
+
+ , "Pipe within text doesn't start a table" =:
+ "Ceci n'est pas une | pipe " =?>
+ para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ])
+
+
+ , "Table with differing row lengths" =:
+ T.unlines [ "|| Numbers | Text "
+ , "| 1 | One | foo |"
+ , "| 2 "
+ ] =?>
+ table "" (zip [AlignCenter, AlignLeft, AlignLeft] [0, 0, 0])
+ [ plain "Numbers", plain "Text" , plain mempty ]
+ [ [ plain "1" , plain "One" , plain "foo" ]
+ , [ plain "2" , plain mempty , plain mempty ]
+ ]
+
+ ]
+
+ , testGroup "Blocks and fragments"
+ [ "Source block" =:
+ T.unlines [ "```"
+ , "main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , "```" ] =?>
+ let code' = "main = putStrLn greeting\n" <>
+ " where greeting = \"moin\"\n"
+ in codeBlock code'
+
+ , "tagged block" =:
+ T.unlines [ "'''"
+ , "<aside>HTML5 is pretty nice.</aside>"
+ , "'''"
+ ] =?>
+ rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
+
+ , "Quote block" =:
+ T.unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!"
+ ] =?>
+ blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
+ , "eine", "Mauer", "zu", "errichten!"
+ ]))
+
+ ]
+ ]
diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs
new file mode 100644
index 000000000..cc448419c
--- /dev/null
+++ b/test/Tests/Shared.hs
@@ -0,0 +1,39 @@
+module Tests.Shared (tests) where
+
+import System.FilePath.Posix (joinPath)
+import Test.Tasty
+import Test.Tasty.HUnit (assertBool, testCase, (@?=))
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+import Text.Pandoc.Shared
+
+tests :: [TestTree]
+tests = [ testGroup "compactifyDL"
+ [ testCase "compactifyDL with empty def" $
+ assertBool "compactifyDL"
+ (let x = [(str "word", [para (str "def"), mempty])]
+ in compactifyDL x == x)
+ ]
+ , testGroup "collapseFilePath" testCollapse
+ ]
+
+testCollapse :: [TestTree]
+testCollapse = map (testCase "collapse")
+ [ collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"])
+ , collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]])
+ , collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"])
+ , collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"])
+ , collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"])
+ , collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"])
+ , collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""])
+ , collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."])
+ , collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."])
+ , collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"])
+ , collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"])
+ , collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"])
+ , collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"])
+ , collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"])]
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
new file mode 100644
index 000000000..6b97c0761
--- /dev/null
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -0,0 +1,56 @@
+module Tests.Writers.AsciiDoc (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+asciidoc :: (ToPandoc a) => a -> String
+asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
+
+tests :: [TestTree]
+tests = [ testGroup "emphasis"
+ [ test asciidoc "emph word before" $
+ para (text "foo" <> emph (text "bar")) =?>
+ "foo__bar__"
+ , test asciidoc "emph word after" $
+ para (emph (text "foo") <> text "bar") =?>
+ "__foo__bar"
+ , test asciidoc "emph quoted" $
+ para (doubleQuoted (emph (text "foo"))) =?>
+ "``__foo__''"
+ , test asciidoc "strong word before" $
+ para (text "foo" <> strong (text "bar")) =?>
+ "foo**bar**"
+ , test asciidoc "strong word after" $
+ para (strong (text "foo") <> text "bar") =?>
+ "**foo**bar"
+ , test asciidoc "strong quoted" $
+ para (singleQuoted (strong (text "foo"))) =?>
+ "`**foo**'"
+ ]
+ , testGroup "tables"
+ [ test asciidoc "empty cells" $
+ simpleTable [] [[mempty],[mempty]] =?> unlines
+ [ "[cols=\"\",]"
+ , "|===="
+ , "|"
+ , "|"
+ , "|===="
+ ]
+ , test asciidoc "multiblock cells" $
+ simpleTable [] [[para (text "Para 1") <> para (text "Para 2")]]
+ =?> unlines
+ [ "[cols=\"\",]"
+ , "|====="
+ , "a|"
+ , "Para 1"
+ , ""
+ , "Para 2"
+ , ""
+ , "|====="
+ ]
+ ]
+ ]
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
new file mode 100644
index 000000000..812aab4a6
--- /dev/null
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -0,0 +1,149 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.ConTeXt (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Test.Tasty.QuickCheck
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+context :: (ToPandoc a) => a -> String
+context = unpack . purely (writeConTeXt def) . toPandoc
+
+context' :: (ToPandoc a) => a -> String
+context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc
+
+contextNtb :: (ToPandoc a) => a -> String
+contextNtb = unpack . purely (writeConTeXt def{ writerExtensions = enableExtension Ext_ntb pandocExtensions }) . toPandoc
+
+contextDiv :: (ToPandoc a) => a -> String
+contextDiv = unpack . purely (writeConTeXt def{ writerSectionDivs = True }) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test context "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test context "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test context
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ "with '}'" =: code "}" =?> "\\mono{\\}}"
+ , "without '}'" =: code "]" =?> "\\type{]}"
+ , testProperty "code property" $ \s -> null s ||
+ if '{' `elem` s || '}' `elem` s
+ then context' (code s) == "\\mono{" ++
+ context' (str s) ++ "}"
+ else context' (code s) == "\\type{" ++ s ++ "}"
+ ]
+ , testGroup "headers"
+ [ "level 1" =:
+ headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[title={My header},reference={my-header}]"
+ , test contextDiv "section-divs" $
+ ( headerWith ("header1", [], []) 1 (text "Header1")
+ <> headerWith ("header2", [], []) 2 (text "Header2")
+ <> headerWith ("header3", [], []) 3 (text "Header3")
+ <> headerWith ("header4", [], []) 4 (text "Header4")
+ <> headerWith ("header5", [], []) 5 (text "Header5")
+ <> headerWith ("header6", [], []) 6 (text "Header6"))
+ =?>
+ unlines [ "\\startsection[title={Header1},reference={header1}]\n"
+ , "\\startsubsection[title={Header2},reference={header2}]\n"
+ , "\\startsubsubsection[title={Header3},reference={header3}]\n"
+ , "\\startsubsubsubsection[title={Header4},reference={header4}]\n"
+ , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n"
+ , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n"
+ , "\\stopsubsubsubsubsubsection\n"
+ , "\\stopsubsubsubsubsection\n"
+ , "\\stopsubsubsubsection\n"
+ , "\\stopsubsubsection\n"
+ , "\\stopsubsection\n"
+ , "\\stopsection" ]
+ ]
+ , testGroup "bullet lists"
+ [ "nested" =:
+ bulletList [
+ plain (text "top")
+ <> bulletList [
+ plain (text "next")
+ <> bulletList [plain (text "bot")]
+ ]
+ ] =?> unlines
+ [ "\\startitemize[packed]"
+ , "\\item"
+ , " top"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " next"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " bot"
+ , " \\stopitemize"
+ , " \\stopitemize"
+ , "\\stopitemize" ]
+ ]
+ , testGroup "natural tables"
+ [ test contextNtb "table with header and caption" $
+ let caption = text "Table 1"
+ aligns = [(AlignRight, 0.0), (AlignLeft, 0.0), (AlignCenter, 0.0), (AlignDefault, 0.0)]
+ headers = [plain $ text "Right",
+ plain $ text "Left",
+ plain $ text "Center",
+ plain $ text "Default"]
+ rows = [[plain $ text "1.1",
+ plain $ text "1.2",
+ plain $ text "1.3",
+ plain $ text "1.4"]
+ ,[plain $ text "2.1",
+ plain $ text "2.2",
+ plain $ text "2.3",
+ plain $ text "2.4"]
+ ,[plain $ text "3.1",
+ plain $ text "3.2",
+ plain $ text "3.3",
+ plain $ text "3.4"]]
+ in table caption aligns headers rows
+ =?> unlines [ "\\startplacetable[title={Table 1}]"
+ , "\\startTABLE"
+ , "\\startTABLEhead"
+ , "\\NC[align=left] Right"
+ , "\\NC[align=right] Left"
+ , "\\NC[align=middle] Center"
+ , "\\NC Default"
+ , "\\NC\\NR"
+ , "\\stopTABLEhead"
+ , "\\startTABLEbody"
+ , "\\NC[align=left] 1.1"
+ , "\\NC[align=right] 1.2"
+ , "\\NC[align=middle] 1.3"
+ , "\\NC 1.4"
+ , "\\NC\\NR"
+ , "\\NC[align=left] 2.1"
+ , "\\NC[align=right] 2.2"
+ , "\\NC[align=middle] 2.3"
+ , "\\NC 2.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEbody"
+ , "\\startTABLEfoot"
+ , "\\NC[align=left] 3.1"
+ , "\\NC[align=right] 3.2"
+ , "\\NC[align=middle] 3.3"
+ , "\\NC 3.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEfoot"
+ , "\\stopTABLE"
+ , "\\stopplacetable" ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs
new file mode 100644
index 000000000..89ea76586
--- /dev/null
+++ b/test/Tests/Writers/Docbook.hs
@@ -0,0 +1,303 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Docbook (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+docbook :: (ToPandoc a) => a -> String
+docbook = docbookWithOpts def{ writerWrapText = WrapNone }
+
+docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
+docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test docbook "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test docbook "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test docbook
+
+lineblock :: Blocks
+lineblock = para ("some text" <> linebreak <>
+ "and more lines" <> linebreak <>
+ "and again")
+lineblock_out :: [String]
+lineblock_out = [ "<literallayout>some text"
+ , "and more lines"
+ , "and again</literallayout>"
+ ]
+
+tests :: [TestTree]
+tests = [ testGroup "line blocks"
+ [ "none" =: para "This is a test"
+ =?> unlines
+ [ "<para>"
+ , " This is a test"
+ , "</para>"
+ ]
+ , "basic" =: lineblock
+ =?> unlines lineblock_out
+ , "blockquote" =: blockQuote lineblock
+ =?> unlines
+ ( [ "<blockquote>" ] ++
+ lineblock_out ++
+ [ "</blockquote>" ]
+ )
+ , "footnote" =: para ("This is a test" <>
+ note lineblock <>
+ " of footnotes")
+ =?> unlines
+ ( [ "<para>"
+ , " This is a test<footnote>" ] ++
+ lineblock_out ++
+ [ " </footnote> of footnotes"
+ , "</para>" ]
+ )
+ ]
+ , testGroup "compact lists"
+ [ testGroup "bullet"
+ [ "compact" =: bulletList [plain "a", plain "b", plain "c"]
+ =?> unlines
+ [ "<itemizedlist spacing=\"compact\">"
+ , " <listitem>"
+ , " <para>"
+ , " a"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " b"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " c"
+ , " </para>"
+ , " </listitem>"
+ , "</itemizedlist>"
+ ]
+ , "loose" =: bulletList [para "a", para "b", para "c"]
+ =?> unlines
+ [ "<itemizedlist>"
+ , " <listitem>"
+ , " <para>"
+ , " a"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " b"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " c"
+ , " </para>"
+ , " </listitem>"
+ , "</itemizedlist>"
+ ]
+ ]
+ , testGroup "ordered"
+ [ "compact" =: orderedList [plain "a", plain "b", plain "c"]
+ =?> unlines
+ [ "<orderedlist spacing=\"compact\">"
+ , " <listitem>"
+ , " <para>"
+ , " a"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " b"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " c"
+ , " </para>"
+ , " </listitem>"
+ , "</orderedlist>"
+ ]
+ , "loose" =: orderedList [para "a", para "b", para "c"]
+ =?> unlines
+ [ "<orderedlist>"
+ , " <listitem>"
+ , " <para>"
+ , " a"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " b"
+ , " </para>"
+ , " </listitem>"
+ , " <listitem>"
+ , " <para>"
+ , " c"
+ , " </para>"
+ , " </listitem>"
+ , "</orderedlist>"
+ ]
+ ]
+ , testGroup "definition"
+ [ "compact" =: definitionList [ ("an", [plain "apple" ])
+ , ("a", [plain "banana"])
+ , ("an", [plain "orange"])]
+ =?> unlines
+ [ "<variablelist spacing=\"compact\">"
+ , " <varlistentry>"
+ , " <term>"
+ , " an"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " apple"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , " <varlistentry>"
+ , " <term>"
+ , " a"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " banana"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , " <varlistentry>"
+ , " <term>"
+ , " an"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " orange"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , "</variablelist>"
+ ]
+ , "loose" =: definitionList [ ("an", [para "apple" ])
+ , ("a", [para "banana"])
+ , ("an", [para "orange"])]
+ =?> unlines
+ [ "<variablelist>"
+ , " <varlistentry>"
+ , " <term>"
+ , " an"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " apple"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , " <varlistentry>"
+ , " <term>"
+ , " a"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " banana"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , " <varlistentry>"
+ , " <term>"
+ , " an"
+ , " </term>"
+ , " <listitem>"
+ , " <para>"
+ , " orange"
+ , " </para>"
+ , " </listitem>"
+ , " </varlistentry>"
+ , "</variablelist>"
+ ]
+ ]
+ ]
+ , testGroup "writer options"
+ [ testGroup "top-level division" $
+ let
+ headers = header 1 (text "header1")
+ <> header 2 (text "header2")
+ <> header 3 (text "header3")
+
+ docbookTopLevelDiv :: (ToPandoc a)
+ => TopLevelDivision -> a -> String
+ docbookTopLevelDiv division =
+ docbookWithOpts def{ writerTopLevelDivision = division }
+ in
+ [ test (docbookTopLevelDiv TopLevelSection) "sections as top-level" $
+ headers =?>
+ unlines [ "<sect1>"
+ , " <title>header1</title>"
+ , " <sect2>"
+ , " <title>header2</title>"
+ , " <sect3>"
+ , " <title>header3</title>"
+ , " <para>"
+ , " </para>"
+ , " </sect3>"
+ , " </sect2>"
+ , "</sect1>"
+ ]
+ , test (docbookTopLevelDiv TopLevelChapter) "chapters as top-level" $
+ headers =?>
+ unlines [ "<chapter>"
+ , " <title>header1</title>"
+ , " <sect1>"
+ , " <title>header2</title>"
+ , " <sect2>"
+ , " <title>header3</title>"
+ , " <para>"
+ , " </para>"
+ , " </sect2>"
+ , " </sect1>"
+ , "</chapter>"
+ ]
+ , test (docbookTopLevelDiv TopLevelPart) "parts as top-level" $
+ headers =?>
+ unlines [ "<part>"
+ , " <title>header1</title>"
+ , " <chapter>"
+ , " <title>header2</title>"
+ , " <sect1>"
+ , " <title>header3</title>"
+ , " <para>"
+ , " </para>"
+ , " </sect1>"
+ , " </chapter>"
+ , "</part>"
+ ]
+ , test (docbookTopLevelDiv TopLevelDefault) "default top-level" $
+ headers =?>
+ unlines [ "<sect1>"
+ , " <title>header1</title>"
+ , " <sect2>"
+ , " <title>header2</title>"
+ , " <sect3>"
+ , " <title>header3</title>"
+ , " <para>"
+ , " </para>"
+ , " </sect3>"
+ , " </sect2>"
+ , "</sect1>"
+ ]
+ ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
new file mode 100644
index 000000000..3ded0aa38
--- /dev/null
+++ b/test/Tests/Writers/Docx.hs
@@ -0,0 +1,157 @@
+module Tests.Writers.Docx (tests) where
+
+import Text.Pandoc
+import Test.Tasty
+import Tests.Writers.OOXML
+import Test.Tasty.HUnit
+import Data.List (isPrefixOf)
+
+-- we add an extra check to make sure that we're not writing in the
+-- toplevel docx directory. We don't want to accidentally overwrite an
+-- Word-generated docx file used to test the reader.
+docxTest :: String -> WriterOptions -> FilePath -> FilePath -> TestTree
+docxTest testName opts nativeFP goldenFP =
+ if "docx/golden/" `isPrefixOf` goldenFP
+ then ooxmlTest writeDocx testName opts nativeFP goldenFP
+ else testCase testName $
+ assertFailure $
+ goldenFP ++ " is not in `test/docx/golden`"
+
+tests :: [TestTree]
+tests = [ testGroup "inlines"
+ [ docxTest
+ "font formatting"
+ def
+ "docx/inline_formatting.native"
+ "docx/golden/inline_formatting.docx"
+ , docxTest
+ "hyperlinks"
+ def
+ "docx/links.native"
+ "docx/golden/links.docx"
+ , docxTest
+ "inline image"
+ def
+ "docx/image_writer_test.native"
+ "docx/golden/image.docx"
+ , docxTest
+ "inline images"
+ def
+ "docx/inline_images_writer_test.native"
+ "docx/golden/inline_images.docx"
+ , docxTest
+ "handling unicode input"
+ def
+ "docx/unicode.native"
+ "docx/golden/unicode.docx"
+ , docxTest
+ "inline code"
+ def
+ "docx/inline_code.native"
+ "docx/golden/inline_code.docx"
+ , docxTest
+ "inline code in subscript and superscript"
+ def
+ "docx/verbatim_subsuper.native"
+ "docx/golden/verbatim_subsuper.docx"
+ ]
+ , testGroup "blocks"
+ [ docxTest
+ "headers"
+ def
+ "docx/headers.native"
+ "docx/golden/headers.docx"
+ , docxTest
+ "nested anchor spans in header"
+ def
+ "docx/nested_anchors_in_header.native"
+ "docx/golden/nested_anchors_in_header.docx"
+ , docxTest
+ "lists"
+ def
+ "docx/lists.native"
+ "docx/golden/lists.docx"
+ , docxTest
+ "lists continuing after interruption"
+ def
+ "docx/lists_continuing.native"
+ "docx/golden/lists_continuing.docx"
+ , docxTest
+ "lists restarting after interruption"
+ def
+ "docx/lists_restarting.native"
+ "docx/golden/lists_restarting.docx"
+ , docxTest
+ "definition lists"
+ def
+ "docx/definition_list.native"
+ "docx/golden/definition_list.docx"
+ , docxTest
+ "footnotes and endnotes"
+ def
+ "docx/notes.native"
+ "docx/golden/notes.docx"
+ , docxTest
+ "links in footnotes and endnotes"
+ def
+ "docx/link_in_notes.native"
+ "docx/golden/link_in_notes.docx"
+ , docxTest
+ "blockquotes"
+ def
+ "docx/block_quotes_parse_indent.native"
+ "docx/golden/block_quotes.docx"
+ , docxTest
+ "tables"
+ def
+ "docx/tables.native"
+ "docx/golden/tables.docx"
+ , docxTest
+ "tables with lists in cells"
+ def
+ "docx/table_with_list_cell.native"
+ "docx/golden/table_with_list_cell.docx"
+ , docxTest
+ "tables with one row"
+ def
+ "docx/table_one_row.native"
+ "docx/golden/table_one_row.docx"
+ , docxTest
+ "code block"
+ def
+ "docx/codeblock.native"
+ "docx/golden/codeblock.docx"
+ ]
+ , testGroup "track changes"
+ [ docxTest
+ "insertion"
+ def
+ "docx/track_changes_insertion_all.native"
+ "docx/golden/track_changes_insertion.docx"
+ , docxTest
+ "deletion"
+ def
+ "docx/track_changes_deletion_all.native"
+ "docx/golden/track_changes_deletion.docx"
+ , docxTest
+ "move text"
+ def
+ "docx/track_changes_move_all.native"
+ "docx/golden/track_changes_move.docx"
+ , docxTest
+ "comments"
+ def
+ "docx/comments.native"
+ "docx/golden/comments.docx"
+ ]
+ , testGroup "custom styles"
+ [ docxTest "custom styles without reference.docx"
+ def
+ "docx/custom_style.native"
+ "docx/golden/custom_style_no_reference.docx"
+ , docxTest "custom styles with reference.docx"
+ def{writerReferenceDoc = Just "docx/custom-style-reference.docx"}
+ "docx/custom_style.native"
+ "docx/golden/custom_style_reference.docx"
+ ]
+ ]
diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs
new file mode 100644
index 000000000..6663c42f8
--- /dev/null
+++ b/test/Tests/Writers/FB2.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.FB2 (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+fb2 :: String -> String
+fb2 x = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n" ++
+ "<FictionBook xmlns=\"http://www.gribuser.ru/xml/fictionbook/2.0\" xmlns:l=\"http://www.w3.org/1999/xlink\"><description><title-info><genre>unrecognised</genre></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><section>" ++ x ++ "</section></body></FictionBook>"
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeFB2 def) . toPandoc)
+
+tests :: [TestTree]
+tests = [ testGroup "block elements"
+ ["para" =: para "Lorem ipsum cetera."
+ =?> fb2 "<p>Lorem ipsum cetera.</p>"
+ ]
+ , testGroup "inlines"
+ [
+ "Emphasis" =: emph "emphasized"
+ =?> fb2 "<emphasis>emphasized</emphasis>"
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> fb2 "<p>\x2022 first</p><p>\x2022 second</p><p>\x2022 third</p>"
+ ]
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
new file mode 100644
index 000000000..23ff718d3
--- /dev/null
+++ b/test/Tests/Writers/HTML.hs
@@ -0,0 +1,44 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.HTML (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+html :: (ToPandoc a) => a -> String
+html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test html "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test html "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test html
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
+ , "haskell" =: codeWith ("",["haskell"],[]) ">>="
+ =?> "<code class=\"sourceCode haskell\"><span class=\"fu\">&gt;&gt;=</span></code>"
+ , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
+ =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
+ ]
+ , testGroup "images"
+ [ "alt with formatting" =:
+ image "/url" "title" ("my " <> emph "image")
+ =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
+ ]
+ ]
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
new file mode 100644
index 000000000..572b16451
--- /dev/null
+++ b/test/Tests/Writers/JATS.hs
@@ -0,0 +1,122 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.JATS (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+jats :: (ToPandoc a) => a -> String
+jats = unpack . purely (writeJATS def{ writerWrapText = WrapNone }) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test jats "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test jats "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test jats
+
+tests :: [TestTree]
+tests = [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<p>\n <monospace>@&amp;</monospace>\n</p>"
+ , "lang" =: codeWith ("", ["c"], []) "@&" =?> "<p>\n <code language=\"c\">@&amp;</code>\n</p>"
+ ]
+ , testGroup "block code"
+ [ "basic" =: codeBlock "@&" =?> "<preformat>@&amp;</preformat>"
+ , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "<code language=\"c\">@&amp;</code>"
+ ]
+ , testGroup "images"
+ [ "basic" =:
+ image "/url" "title" mempty
+ =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ ]
+ , testGroup "inlines"
+ [ "Emphasis" =: emph "emphasized"
+ =?> "<p>\n <italic>emphasized</italic>\n</p>"
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ first\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ second\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>\n\
+ \ third\n\
+ \ </p>\n\
+ \ </list-item>\n\
+ \</list>"
+ , testGroup "definition lists"
+ [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
+ [plain (text "hi there")])] =?>
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term>\n\
+ \ <xref alt=\"testing\" rid=\"go\">testing</xref>\n\
+ \ </term>\n\
+ \ <def>\n\
+ \ <p>\n\
+ \ hi there\n\
+ \ </p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ ]
+ , testGroup "math"
+ [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
+ "<p>\n\
+ \ <inline-formula><alternatives>\n\
+ \ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \ <mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula>\n\
+ \</p>"
+ ]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header 1<fn>\n\
+ \ <p>\n\
+ \ note\n\
+ \ </p>\n\
+ \ </fn></title>\n\
+ \</sec>"
+ , "unnumbered sub header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header")
+ <> headerWith ("foo",["unnumbered"],[]) 2
+ (text "Sub-Header") =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ ]
+ ]
diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs
new file mode 100644
index 000000000..471d9d9e7
--- /dev/null
+++ b/test/Tests/Writers/LaTeX.hs
@@ -0,0 +1,176 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.LaTeX (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+latex :: (ToPandoc a) => a -> String
+latex = latexWithOpts def
+
+latexListing :: (ToPandoc a) => a -> String
+latexListing = latexWithOpts def{ writerListings = True }
+
+latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+latexWithOpts opts = unpack . purely (writeLaTeX opts) . toPandoc
+
+beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+beamerWithOpts opts = unpack . purely (writeBeamer opts) . toPandoc
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test latex "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test latex "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test latex
+
+tests :: [TestTree]
+tests = [ testGroup "code blocks"
+ [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?>
+ "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}"
+ , test latexListing "identifier" $ codeBlockWith ("id",[],[]) "hi" =?>
+ ("\\begin{lstlisting}[label=id]\nhi\n\\end{lstlisting}" :: String)
+ , test latexListing "no identifier" $ codeBlock "hi" =?>
+ ("\\begin{lstlisting}\nhi\n\\end{lstlisting}" :: String)
+ ]
+ , testGroup "definition lists"
+ [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
+ [plain (text "hi there")])] =?>
+ "\\begin{description}\n\\tightlist\n\\item[{\\protect\\hyperlink{go}{testing}}]\nhi there\n\\end{description}"
+ ]
+ , testGroup "math"
+ [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
+ "\\(\\sigma|_{\\{x\\}}\\)"
+ ]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "\\hypertarget{foo}{%\n\\section*{\\texorpdfstring{Header 1\\footnote{note}}{Header 1}}\\label{foo}}\n\\addcontentsline{toc}{section}{Header 1}\n"
+ , "in list item" =:
+ bulletList [header 2 (text "foo")] =?>
+ "\\begin{itemize}\n\\item ~\n \\subsection{foo}\n\\end{itemize}"
+ , "in definition list item" =:
+ definitionList [(text "foo", [header 2 (text "bar"),
+ para $ text "baz"])] =?>
+ "\\begin{description}\n\\item[foo] ~ \n\\subsection{bar}\n\nbaz\n\\end{description}"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "\\section{\\texorpdfstring{\\protect\\includegraphics{imgs/foo.jpg}}{Alt text}}"
+ ]
+ , testGroup "inline code"
+ [ "struck out and highlighted" =:
+ strikeout (codeWith ("",["haskell"],[]) "foo" <> space
+ <> str "bar") =?>
+ "\\sout{\\mbox{\\VERB|\\NormalTok{foo}|} bar}"
+ , "struck out and not highlighted" =:
+ strikeout (code "foo" <> space
+ <> str "bar") =?>
+ "\\sout{\\texttt{foo} bar}"
+ , "single quotes" =:
+ code "dog's" =?> "\\texttt{dog\\textquotesingle{}s}"
+ , "backtick" =:
+ code "`nu?`" =?> "\\texttt{\\textasciigrave{}nu?\\textasciigrave{}}"
+ ]
+ , testGroup "writer options"
+ [ testGroup "top-level division" $
+ let
+ headers = header 1 (text "header1")
+ <> header 2 (text "header2")
+ <> header 3 (text "header3")
+
+ latexTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String
+ latexTopLevelDiv division =
+ latexWithOpts def{ writerTopLevelDivision = division }
+
+ beamerTopLevelDiv :: (ToPandoc a)
+ => TopLevelDivision -> a -> String
+ beamerTopLevelDiv division =
+ beamerWithOpts def { writerTopLevelDivision = division }
+ in
+ [ test (latexTopLevelDiv TopLevelSection)
+ "sections as top-level" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (latexTopLevelDiv TopLevelChapter)
+ "chapters as top-level" $ headers =?>
+ unlines [ "\\chapter{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ , test (latexTopLevelDiv TopLevelPart)
+ "parts as top-level" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\chapter{header2}\n"
+ , "\\section{header3}"
+ ]
+ , test (latexTopLevelDiv TopLevelDefault)
+ "default top-level" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (beamerTopLevelDiv TopLevelSection)
+ "sections as top-level in beamer" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (beamerTopLevelDiv TopLevelChapter)
+ "chapters are as part in beamer" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ , test (beamerTopLevelDiv TopLevelPart)
+ "parts as top-level in beamer" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ , test (beamerTopLevelDiv TopLevelDefault)
+ "default top-level in beamer" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (latexTopLevelDiv TopLevelPart)
+ "part top-level, section not in toc" $
+ ( headerWith ("", ["unnumbered"], []) 1 (text "header1")
+ <> headerWith ("", ["unnumbered"], []) 2 (text "header2")
+ <> headerWith ("", ["unnumbered"], []) 3 (text "header3")
+ <> headerWith ("", ["unnumbered"], []) 4 (text "header4")
+ <> headerWith ("", ["unnumbered"], []) 5 (text "header5")
+ <> headerWith ("", ["unnumbered"], []) 6 (text "header6"))
+ =?>
+ unlines [ "\\part*{header1}"
+ , "\\addcontentsline{toc}{part}{header1}\n"
+ , "\\chapter*{header2}"
+ , "\\addcontentsline{toc}{chapter}{header2}\n"
+ , "\\section*{header3}"
+ , "\\addcontentsline{toc}{section}{header3}\n"
+ , "\\subsection*{header4}"
+ , "\\addcontentsline{toc}{subsection}{header4}\n"
+ , "\\subsubsection*{header5}"
+ , "\\addcontentsline{toc}{subsubsection}{header5}\n"
+ , "\\paragraph{header6}"
+ , "\\addcontentsline{toc}{paragraph}{header6}"
+ ]
+ ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs
new file mode 100644
index 000000000..7f9ac3627
--- /dev/null
+++ b/test/Tests/Writers/Markdown.hs
@@ -0,0 +1,267 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
+module Tests.Writers.Markdown (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+defopts :: WriterOptions
+defopts = def{ writerExtensions = pandocExtensions }
+
+markdown :: (ToPandoc a) => a -> String
+markdown = unpack . purely (writeMarkdown defopts) . toPandoc
+
+markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test markdown "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test markdown "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test markdown
+
+tests :: [TestTree]
+tests = [ "indented code after list"
+ =: (orderedList [ para "one" <> para "two" ] <> codeBlock "test")
+ =?> "1. one\n\n two\n\n<!-- -->\n\n test"
+ , "list with tight sublist"
+ =: bulletList [ plain "foo" <> bulletList [ plain "bar" ],
+ plain "baz" ]
+ =?> "- foo\n - bar\n- baz\n"
+ ] ++ [noteTests] ++ [shortcutLinkRefsTests]
+
+{-
+
+Testing with the following text:
+
+First Header
+============
+
+This is a footnote.[^1] And this is a [link](https://www.google.com).
+
+> A note inside a block quote.[^2]
+>
+> A second paragraph.
+
+Second Header
+=============
+
+Some more text.
+
+
+[^1]: Down here.
+
+[^2]: The second note.
+
+-}
+
+noteTestDoc :: Blocks
+noteTestDoc =
+ header 1 "First Header" <>
+ para ("This is a footnote." <>
+ note (para "Down here.") <>
+ " And this is a " <>
+ link "https://www.google.com" "" "link" <>
+ ".") <>
+ blockQuote (para ("A note inside a block quote." <>
+ note (para "The second note.")) <>
+ para "A second paragraph.") <>
+ header 1 "Second Header" <>
+ para "Some more text."
+
+
+
+noteTests :: TestTree
+noteTests = testGroup "note and reference location"
+ [ test (markdownWithOpts defopts)
+ "footnotes at the end of a document" $
+ noteTestDoc =?>
+ (unlines [ "First Header"
+ , "============"
+ , ""
+ , "This is a footnote.[^1] And this is a [link](https://www.google.com)."
+ , ""
+ , "> A note inside a block quote.[^2]"
+ , ">"
+ , "> A second paragraph."
+ , ""
+ , "Second Header"
+ , "============="
+ , ""
+ , "Some more text."
+ , ""
+ , "[^1]: Down here."
+ , ""
+ , "[^2]: The second note."
+ ])
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock})
+ "footnotes at the end of blocks" $
+ noteTestDoc =?>
+ (unlines [ "First Header"
+ , "============"
+ , ""
+ , "This is a footnote.[^1] And this is a [link](https://www.google.com)."
+ , ""
+ , "[^1]: Down here."
+ , ""
+ , "> A note inside a block quote.[^2]"
+ , ">"
+ , "> A second paragraph."
+ , ""
+ , "[^2]: The second note."
+ , ""
+ , "Second Header"
+ , "============="
+ , ""
+ , "Some more text."
+ ])
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True})
+ "footnotes and reference links at the end of blocks" $
+ noteTestDoc =?>
+ (unlines [ "First Header"
+ , "============"
+ , ""
+ , "This is a footnote.[^1] And this is a [link]."
+ , ""
+ , "[^1]: Down here."
+ , ""
+ , " [link]: https://www.google.com"
+ , ""
+ , "> A note inside a block quote.[^2]"
+ , ">"
+ , "> A second paragraph."
+ , ""
+ , "[^2]: The second note."
+ , ""
+ , "Second Header"
+ , "============="
+ , ""
+ , "Some more text."
+ ])
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection})
+ "footnotes at the end of section" $
+ noteTestDoc =?>
+ (unlines [ "First Header"
+ , "============"
+ , ""
+ , "This is a footnote.[^1] And this is a [link](https://www.google.com)."
+ , ""
+ , "> A note inside a block quote.[^2]"
+ , ">"
+ , "> A second paragraph."
+ , ""
+ , "[^1]: Down here."
+ , ""
+ , "[^2]: The second note."
+ , ""
+ , "Second Header"
+ , "============="
+ , ""
+ , "Some more text."
+ ])
+
+ ]
+
+shortcutLinkRefsTests :: TestTree
+shortcutLinkRefsTests =
+ let infix 4 =:
+ (=:) :: (ToString a, ToPandoc a)
+
+ => String -> (a, String) -> TestTree
+ (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc)
+ in testGroup "Shortcut reference links"
+ [ "Simple link (shortcutable)"
+ =: para (link "/url" "title" "foo")
+ =?> "[foo]\n\n [foo]: /url \"title\""
+ , "Followed by another link (unshortcutable)"
+ =: para ((link "/url1" "title1" "first")
+ <> (link "/url2" "title2" "second"))
+ =?> unlines [ "[first][][second]"
+ , ""
+ , " [first]: /url1 \"title1\""
+ , " [second]: /url2 \"title2\""
+ ]
+ , "Followed by space and another link (unshortcutable)"
+ =: para ((link "/url1" "title1" "first") <> " "
+ <> (link "/url2" "title2" "second"))
+ =?> unlines [ "[first][] [second]"
+ , ""
+ , " [first]: /url1 \"title1\""
+ , " [second]: /url2 \"title2\""
+ ]
+ , "Reference link is used multiple times (unshortcutable)"
+ =: para ((link "/url1" "" "foo") <> (link "/url2" "" "foo")
+ <> (link "/url3" "" "foo"))
+ =?> unlines [ "[foo][][foo][1][foo][2]"
+ , ""
+ , " [foo]: /url1"
+ , " [1]: /url2"
+ , " [2]: /url3"
+ ]
+ , "Reference link is used multiple times (unshortcutable)"
+ =: para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo")
+ <> " " <> (link "/url3" "" "foo"))
+ =?> unlines [ "[foo][] [foo][1] [foo][2]"
+ , ""
+ , " [foo]: /url1"
+ , " [1]: /url2"
+ , " [2]: /url3"
+ ]
+ , "Reference link is followed by text in brackets"
+ =: para ((link "/url" "" "link") <> "[text in brackets]")
+ =?> unlines [ "[link][]\\[text in brackets\\]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and text in brackets"
+ =: para ((link "/url" "" "link") <> " [text in brackets]")
+ =?> unlines [ "[link][] \\[text in brackets\\]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by RawInline"
+ =: para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]")
+ =?> unlines [ "[link][][rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and RawInline"
+ =: para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]")
+ =?> unlines [ "[link][] [rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by RawInline with space"
+ =: para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]")
+ =?> unlines [ "[link][] [rawText]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by citation"
+ =: para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))
+ =?> unlines [ "[link][][@author]"
+ , ""
+ , " [link]: /url"
+ ]
+ , "Reference link is followed by space and citation"
+ =: para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))
+ =?> unlines [ "[link][] [@author]"
+ , ""
+ , " [link]: /url"
+ ]
+ ]
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
new file mode 100644
index 000000000..0b8a08258
--- /dev/null
+++ b/test/Tests/Writers/Muse.hs
@@ -0,0 +1,385 @@
+module Tests.Writers.Muse (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+muse :: (ToPandoc a) => a -> String
+muse = museWithOpts def{ writerWrapText = WrapNone,
+ writerExtensions = extensionsFromList [Ext_amuse,
+ Ext_auto_identifiers] }
+
+museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test muse
+
+tests :: [TestTree]
+tests = [ testGroup "block elements"
+ [ "plain" =: plain (text "Foo bar.") =?> "Foo bar."
+ , testGroup "paragraphs"
+ [ "single paragraph" =: para (text "Sample paragraph.")
+ =?> "Sample paragraph."
+ , "two paragraphs" =: para (text "First paragraph.") <>
+ para (text "Second paragraph.")
+ =?> unlines [ "First paragraph."
+ , ""
+ , "Second paragraph."
+ ]
+ ]
+ , "line block" =: lineBlock [text "Foo", text "bar", text "baz"]
+ =?> unlines [ "> Foo"
+ , "> bar"
+ , "> baz"
+ ]
+ , "code block" =: codeBlock "int main(void) {\n\treturn 0;\n}"
+ =?> unlines [ "<example>"
+ , "int main(void) {"
+ , "\treturn 0;"
+ , "}"
+ , "</example>"
+ ]
+ , "html raw block" =: rawBlock "html" "<hr>"
+ =?> unlines [ "<literal style=\"html\">"
+ , "<hr>"
+ , "</literal>"
+ ]
+ , "block quote" =: blockQuote (para (text "Foo"))
+ =?> unlines [ "<quote>"
+ , "Foo"
+ , "</quote>"
+ ]
+ , testGroup "lists"
+ [ testGroup "simple lists"
+ [
+ "ordered list" =: orderedList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> unlines [ " 1. first"
+ , " 2. second"
+ , " 3. third"
+ ]
+ , "ordered list with Roman numerals"
+ =: orderedListWith (1, UpperRoman, DefaultDelim)
+ [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> unlines [ " I. first"
+ , " II. second"
+ , " III. third"
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> unlines [ " - first"
+ , " - second"
+ , " - third"
+ ]
+ , "definition list" =: definitionList [ (text "first definition", [plain $ text "first description"])
+ , (text "second definition", [plain $ text "second description"])
+ , (text "third definition", [plain $ text "third description"])
+ ]
+ =?> unlines [ " first definition :: first description"
+ , " second definition :: second description"
+ , " third definition :: third description"
+ ]
+ , "definition list with multiple descriptions" =:
+ definitionList [ (text "first definition", [plain $ text "first description"
+ ,plain $ text "second description"])
+ , (text "second definition", [plain $ text "third description"])
+ ]
+ =?> unlines [ " first definition :: first description"
+ , " :: second description"
+ , " second definition :: third description"
+ ]
+ ]
+ -- Test that lists of the same type and style are separated with two blanklines
+ , testGroup "sequential lists"
+ [ "bullet lists" =:
+ bulletList [ para $ text "First"
+ , para $ text "Second"
+ , para $ text "Third"
+ ] <>
+ bulletList [ para $ text "Fourth"
+ , para $ text "Fifth"
+ ] =?>
+ unlines [ " - First"
+ , " - Second"
+ , " - Third"
+ , ""
+ , ""
+ , " - Fourth"
+ , " - Fifth"
+ ]
+ , "ordered lists of the same style" =:
+ orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First"
+ , para $ text "Second"
+ ] <>
+ orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third"
+ , para $ text "Fourth"
+ ] =?>
+ unlines [ " I. First"
+ , " II. Second"
+ , ""
+ , ""
+ , " I. Third"
+ , " II. Fourth"
+ ]
+ , "ordered lists with equal styles" =:
+ orderedList [ para $ text "First"
+ , para $ text "Second"
+ ] <>
+ orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third"
+ , para $ text "Fourth"
+ ] =?>
+ unlines [ " 1. First"
+ , " 2. Second"
+ , ""
+ , ""
+ , " 1. Third"
+ , " 2. Fourth"
+ ]
+ , "bullet and ordered lists" =:
+ bulletList [ para $ text "First"
+ , para $ text "Second"
+ ] <>
+ orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "Third"
+ , para $ text "Fourth"
+ ] =?>
+ unlines [ " - First"
+ , " - Second"
+ , ""
+ , " I. Third"
+ , " II. Fourth"
+ ]
+ , "different style ordered lists" =:
+ orderedListWith (1, UpperRoman, DefaultDelim) [ para $ text "First"
+ , para $ text "Second"
+ ] <>
+ orderedListWith (1, Decimal, DefaultDelim) [ para $ text "Third"
+ , para $ text "Fourth"
+ ] =?>
+ unlines [ " I. First"
+ , " II. Second"
+ , ""
+ , " 1. Third"
+ , " 2. Fourth"
+ ]
+ ]
+ , testGroup "nested lists"
+ [ "nested ordered list" =: orderedList [ plain $ text "First outer"
+ , plain (text "Second outer:") <>
+ orderedList [ plain $ text "first"
+ , plain $ text "second"
+ ]
+ , plain $ text "Third outer"
+ ]
+ =?> unlines [ " 1. First outer"
+ , " 2. Second outer:"
+ , " 1. first"
+ , " 2. second"
+ , " 3. Third outer"
+ ]
+ , "nested bullet lists" =: bulletList [ plain $ text "First outer"
+ , plain (text "Second outer:") <>
+ bulletList [ plain $ text "first"
+ , plain $ text "second"
+ ]
+ , plain $ text "Third outer"
+ ]
+ =?> unlines [ " - First outer"
+ , " - Second outer:"
+ , " - first"
+ , " - second"
+ , " - Third outer"
+ ]
+ , "nested definition lists" =: definitionList [ (text "first definition", [plain $ text "first description"])
+ , (text "second definition",
+ [ plain (text "second description") <>
+ definitionList [ ( text "first inner definition"
+ , [plain $ text "first inner description"])
+ , ( text "second inner definition"
+ , [plain $ text "second inner description"])
+ ]
+ ]
+ )
+ ]
+ =?> unlines [ " first definition :: first description"
+ , " second definition :: second description"
+ , " first inner definition :: first inner description"
+ , " second inner definition :: second inner description"
+ ]
+ ]
+ -- Check that list is intended with one space even inside a quote
+ , "List inside block quote" =: blockQuote (orderedList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ])
+ =?> unlines [ "<quote>"
+ , " 1. first"
+ , " 2. second"
+ , " 3. third"
+ , "</quote>"
+ ]
+ ]
+ , testGroup "headings"
+ [ "normal heading" =:
+ header 1 (text "foo") =?> "* foo"
+ , "heading levels" =:
+ header 1 (text "First level") <>
+ header 3 (text "Third level") =?>
+ unlines [ "* First level"
+ , ""
+ , "*** Third level"
+ ]
+ , "heading with ID" =:
+ headerWith ("bar", [], []) 2 (text "Foo") =?>
+ unlines [ "** Foo"
+ , "#bar"
+ ]
+ ]
+ , "horizontal rule" =: horizontalRule =?> "----"
+ , "escape horizontal rule" =: para (text "----") =?> "<verbatim>----</verbatim>"
+ , "escape nonbreaking space" =: para (text "~~") =?> "<verbatim>~~</verbatim>"
+ , testGroup "tables"
+ [ "table without header" =:
+ let rows = [[para $ text "Para 1.1", para $ text "Para 1.2"]
+ ,[para $ text "Para 2.1", para $ text "Para 2.2"]]
+ in simpleTable [] rows
+ =?>
+ unlines [ " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
+ ]
+ , "table with header" =:
+ let headers = [plain $ text "header 1", plain $ text "header 2"]
+ rows = [[para $ text "Para 1.1", para $ text "Para 1.2"]
+ ,[para $ text "Para 2.1", para $ text "Para 2.2"]]
+ in simpleTable headers rows
+ =?>
+ unlines [ " header 1 || header 2"
+ , " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
+ ]
+ , "table with header and caption" =:
+ let caption = text "Table 1"
+ headers = [plain $ text "header 1", plain $ text "header 2"]
+ rows = [[para $ text "Para 1.1", para $ text "Para 1.2"]
+ ,[para $ text "Para 2.1", para $ text "Para 2.2"]]
+ in table caption mempty headers rows
+ =?> unlines [ " header 1 || header 2"
+ , " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
+ , " |+ Table 1 +|"
+ ]
+ ]
+ , "div with bullet list" =:
+ divWith nullAttr (bulletList [para $ text "foo"]) =?>
+ unlines [ " - foo" ] -- Making sure bullets are indented
+ -- Null is trivial
+ ]
+ , testGroup "inline elements"
+ [ testGroup "string"
+ [ "string" =: str "foo" =?> "foo"
+ , "escape footnote" =: str "[1]" =?> "<verbatim>[1]</verbatim>"
+ , "escape verbatim close tag" =: str "foo</verbatim>bar"
+ =?> "<verbatim>foo<</verbatim><verbatim>/verbatim>bar</verbatim>"
+ , "escape pipe to avoid accidental tables" =: str "foo | bar"
+ =?> "<verbatim>foo | bar</verbatim>"
+ , "escape hash to avoid accidental anchors" =: text "#foo bar"
+ =?> "<verbatim>#foo</verbatim> bar"
+ , "escape definition list markers" =: str "::" =?> "<verbatim>::</verbatim>"
+ , "normalize strings before escaping" =: fromList [Str ":", Str ":"] =?> "<verbatim>::</verbatim>"
+ -- We don't want colons to be escaped if they can't be confused
+ -- with definition list item markers.
+ , "do not escape colon" =: str ":" =?> ":"
+ ]
+ , testGroup "emphasis"
+ [ "emph" =: emph (text "foo") =?> "<em>foo</em>"
+ , "strong" =: strong (text "foo") =?> "<strong>foo</strong>"
+ , "strikeout" =: strikeout (text "foo") =?> "<del>foo</del>"
+ ]
+ , "superscript" =: superscript (text "foo") =?> "<sup>foo</sup>"
+ , "subscript" =: subscript (text "foo") =?> "<sub>foo</sub>"
+ , "smallcaps" =: smallcaps (text "foo") =?> "foo"
+ , "single quoted" =: singleQuoted (text "foo") =?> "‘foo’"
+ , "double quoted" =: doubleQuoted (text "foo") =?> "“foo”"
+ -- Cite is trivial
+ , testGroup "code"
+ [ "simple" =: code "foo" =?> "<code>foo</code>"
+ , "escape tag" =: code "<code>foo = bar</code> baz" =?> "<code><code>foo = bar<</code><code>/code> baz</code>"
+ , "normalization with attributes" =: codeWith ("",["haskell"],[]) "foo" <> code "bar" =?> "<code>foobar</code>"
+ , "normalization" =: code "</co" <> code "de>" =?> "<code><</code><code>/code></code>"
+ , "normalization with empty string" =: code "</co" <> str "" <> code "de>" =?> "<code><</code><code>/code></code>"
+ ]
+ , testGroup "spaces"
+ [ "space" =: text "a" <> space <> text "b" =?> "a b"
+ , "soft break" =: text "a" <> softbreak <> text "b" =?> "a b"
+ , test (museWithOpts def{ writerWrapText = WrapPreserve })
+ "preserve soft break" $ text "a" <> softbreak <> text "b"
+ =?> "a\nb"
+ , "line break" =: text "a" <> linebreak <> text "b" =?> "a<br>\nb"
+ ]
+ , testGroup "math"
+ [ "inline math" =: math "2^3" =?> "2<sup>3</sup>"
+ , "display math" =: displayMath "2^3" =?> "2<sup>3</sup>"
+ , "multiple letters in inline math" =: math "abc" =?> "<em>abc</em>"
+ ]
+ , "raw inline"
+ =: rawInline "html" "<mark>marked text</mark>"
+ =?> "<literal style=\"html\"><mark>marked text</mark></literal>"
+ , testGroup "links"
+ [ "link with description" =: link "https://example.com" "" (str "Link 1")
+ =?> "[[https://example.com][Link 1]]"
+ , "link without description" =: link "https://example.com" "" (str "https://example.com")
+ =?> "[[https://example.com]]"
+ -- Internal links in Muse include '#'
+ , "link to anchor" =: link "#intro" "" (str "Introduction")
+ =?> "[[#intro][Introduction]]"
+ -- According to Emacs Muse manual, links to images should be prefixed with "URL:"
+ , "link to image with description" =: link "1.png" "" (str "Link to image")
+ =?> "[[URL:1.png][Link to image]]"
+ , "link to image without description" =: link "1.png" "" (str "1.png")
+ =?> "[[URL:1.png]]"
+ ]
+ , "image" =: image "image.png" "Image 1" (str "") =?> "[[image.png][Image 1]]"
+ , "image with width" =:
+ imageWith ("", [], [("width", "60%")]) "image.png" "Image" (str "") =?>
+ "[[image.png 60][Image]]"
+ , "note" =: note (plain (text "Foo"))
+ =?> unlines [ "[1]"
+ , ""
+ , "[1] Foo"
+ ]
+ , "span" =: spanWith ("",["foobar"],[]) (str "Some text")
+ =?> "<class name=\"foobar\">Some text</class>"
+ , testGroup "combined"
+ [ "emph word before" =:
+ para (text "foo" <> emph (text "bar")) =?>
+ "foo<em>bar</em>"
+ , "emph word after" =:
+ para (emph (text "foo") <> text "bar") =?>
+ "<em>foo</em>bar"
+ , "emph quoted" =:
+ para (doubleQuoted (emph (text "foo"))) =?>
+ "“<em>foo</em>”"
+ , "strong word before" =:
+ para (text "foo" <> strong (text "bar")) =?>
+ "foo<strong>bar</strong>"
+ , "strong word after" =:
+ para (strong (text "foo") <> text "bar") =?>
+ "<strong>foo</strong>bar"
+ , "strong quoted" =:
+ para (singleQuoted (strong (text "foo"))) =?>
+ "‘<strong>foo</strong>’"
+ ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs
new file mode 100644
index 000000000..0c4bf7623
--- /dev/null
+++ b/test/Tests/Writers/Native.hs
@@ -0,0 +1,22 @@
+module Tests.Writers.Native (tests) where
+
+import Data.Text (unpack)
+import Test.Tasty
+import Test.Tasty.QuickCheck
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+
+p_write_rt :: Pandoc -> Bool
+p_write_rt d =
+ read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d
+
+p_write_blocks_rt :: [Block] -> Bool
+p_write_blocks_rt bs =
+ read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs
+
+tests :: [TestTree]
+tests = [ testProperty "p_write_rt" p_write_rt
+ , testProperty "p_write_blocks_rt" $ mapSize
+ (\x -> if x > 3 then 3 else x) p_write_blocks_rt
+ ]
diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs
new file mode 100644
index 000000000..bdfdea145
--- /dev/null
+++ b/test/Tests/Writers/OOXML.hs
@@ -0,0 +1,184 @@
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE OverloadedStrings #-}
+
+module Tests.Writers.OOXML (ooxmlTest) where
+
+import Text.Pandoc
+import Test.Tasty
+import Test.Tasty.Golden.Advanced
+import Codec.Archive.Zip
+import Text.XML.Light
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.Lazy as BL
+import qualified Data.Text.IO as T
+import Data.List (isSuffixOf, sort, (\\), intercalate, union)
+import Data.Maybe (catMaybes, mapMaybe)
+import Tests.Helpers
+import Data.Algorithm.Diff
+import System.FilePath.Glob (compile, match)
+
+compareXMLBool :: Content -> Content -> Bool
+-- We make a special exception for times at the moment, and just pass
+-- them because we can't control the utctime when running IO. Besides,
+-- so long as we have two times, we're okay.
+compareXMLBool (Elem myElem) (Elem goodElem)
+ | (QName "created" _ (Just "dcterms")) <- elName myElem
+ , (QName "created" _ (Just "dcterms")) <- elName goodElem =
+ True
+compareXMLBool (Elem myElem) (Elem goodElem)
+ | (QName "modified" _ (Just "dcterms")) <- elName myElem
+ , (QName "modified" _ (Just "dcterms")) <- elName goodElem =
+ True
+compareXMLBool (Elem myElem) (Elem goodElem) =
+ elName myElem == elName goodElem &&
+ elAttribs myElem == elAttribs goodElem &&
+ and (zipWith compareXMLBool (elContent myElem) (elContent goodElem))
+compareXMLBool (Text myCData) (Text goodCData) =
+ cdVerbatim myCData == cdVerbatim goodCData &&
+ cdData myCData == cdData goodCData &&
+ cdLine myCData == cdLine goodCData
+compareXMLBool (CRef myStr) (CRef goodStr) =
+ myStr == goodStr
+compareXMLBool _ _ = False
+
+displayDiff :: Content -> Content -> String
+displayDiff elemA elemB =
+ showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)
+
+goldenArchive :: FilePath -> IO Archive
+goldenArchive fp = (toArchive . BL.fromStrict) <$> BS.readFile fp
+
+testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString)
+ -> WriterOptions
+ -> FilePath
+ -> IO Archive
+testArchive writerFn opts fp = do
+ txt <- T.readFile fp
+ bs <- runIOorExplode $ readNative def txt >>= writerFn opts
+ return $ toArchive bs
+
+compareFileList :: FilePath -> Archive -> Archive -> Maybe String
+compareFileList goldenFP goldenArch testArch =
+ let testFiles = filesInArchive testArch
+ goldenFiles = filesInArchive goldenArch
+ diffTestGolden = testFiles \\ goldenFiles
+ diffGoldenTest = goldenFiles \\ testFiles
+
+ results =
+ [ if null diffGoldenTest
+ then Nothing
+ else Just $
+ "Files in " ++ goldenFP ++ " but not in generated archive:\n" ++
+ intercalate ", " diffGoldenTest
+ , if null diffTestGolden
+ then Nothing
+ else Just $
+ "Files in generated archive but not in " ++ goldenFP ++ ":\n" ++
+ intercalate ", " diffTestGolden
+ ]
+ in
+ if null $ catMaybes results
+ then Nothing
+ else Just $ intercalate "\n" $ catMaybes results
+
+compareXMLFile' :: FilePath -> Archive -> Archive -> Either String ()
+compareXMLFile' fp goldenArch testArch = do
+ testEntry <- case findEntryByPath fp testArch of
+ Just entry -> Right entry
+ Nothing -> Left $
+ "Can't extract " ++ fp ++ " from generated archive"
+ testXMLDoc <- case parseXMLDoc $ fromEntry testEntry of
+ Just doc -> Right doc
+ Nothing -> Left $
+ "Can't parse xml in " ++ fp ++ " from generated archive"
+
+ goldenEntry <- case findEntryByPath fp goldenArch of
+ Just entry -> Right entry
+ Nothing -> Left $
+ "Can't extract " ++ fp ++ " from archive in stored file"
+ goldenXMLDoc <- case parseXMLDoc $ fromEntry goldenEntry of
+ Just doc -> Right doc
+ Nothing -> Left $
+ "Can't parse xml in " ++ fp ++ " from archive in stored file"
+
+ let testContent = Elem testXMLDoc
+ goldenContent = Elem goldenXMLDoc
+
+ if compareXMLBool goldenContent testContent
+ then Right ()
+ else Left $
+ "Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff testContent goldenContent
+
+compareXMLFile :: FilePath -> Archive -> Archive -> Maybe String
+compareXMLFile fp goldenArch testArch =
+ case compareXMLFile' fp goldenArch testArch of
+ Right _ -> Nothing
+ Left s -> Just s
+
+compareAllXMLFiles :: Archive -> Archive -> Maybe String
+compareAllXMLFiles goldenArch testArch =
+ let allFiles = filesInArchive goldenArch `union` filesInArchive testArch
+ allXMLFiles = sort $
+ filter
+ (\fp -> ".xml" `isSuffixOf` fp || ".rels" `isSuffixOf` fp)
+ allFiles
+ results =
+ mapMaybe (\fp -> compareXMLFile fp goldenArch testArch) allXMLFiles
+ in
+ if null results
+ then Nothing
+ else Just $ unlines results
+
+compareMediaFile' :: FilePath -> Archive -> Archive -> Either String ()
+compareMediaFile' fp goldenArch testArch = do
+ testEntry <- case findEntryByPath fp testArch of
+ Just entry -> Right entry
+ Nothing -> Left $
+ "Can't extract " ++ fp ++ " from generated archive"
+ goldenEntry <- case findEntryByPath fp goldenArch of
+ Just entry -> Right entry
+ Nothing -> Left $
+ "Can't extract " ++ fp ++ " from archive in stored file"
+
+ if fromEntry testEntry == fromEntry goldenEntry
+ then Right ()
+ else Left $
+ "Non-matching binary file: " ++ fp
+
+compareMediaFile :: FilePath -> Archive -> Archive -> Maybe String
+compareMediaFile fp goldenArch testArch =
+ case compareMediaFile' fp goldenArch testArch of
+ Right _ -> Nothing
+ Left s -> Just s
+
+compareAllMediaFiles :: Archive -> Archive -> Maybe String
+compareAllMediaFiles goldenArch testArch =
+ let allFiles = filesInArchive goldenArch `union` filesInArchive testArch
+ mediaPattern = compile "*/media/*"
+ allMediaFiles = sort $
+ filter (match mediaPattern) allFiles
+ results =
+ mapMaybe (\fp -> compareMediaFile fp goldenArch testArch) allMediaFiles
+ in
+ if null results
+ then Nothing
+ else Just $ unlines results
+
+ooxmlTest :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString)
+ -> String
+ -> WriterOptions
+ -> FilePath
+ -> FilePath
+ -> TestTree
+ooxmlTest writerFn testName opts nativeFP goldenFP =
+ goldenTest
+ testName
+ (goldenArchive goldenFP)
+ (testArchive writerFn opts nativeFP)
+ (\goldenArch testArch ->
+ let res = catMaybes [ compareFileList goldenFP goldenArch testArch
+ , compareAllXMLFiles goldenArch testArch
+ , compareAllMediaFiles goldenArch testArch
+ ]
+ in return $ if null res then Nothing else Just $ unlines res)
+ (\a -> BL.writeFile goldenFP $ fromArchive a)
diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs
new file mode 100644
index 000000000..9cbe360da
--- /dev/null
+++ b/test/Tests/Writers/Org.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Org (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeOrg def . toPandoc))
+
+tests :: [TestTree]
+tests = [ testGroup "links"
+ -- See http://orgmode.org/manual/Internal-links.html#Internal-links
+ [ "simple link"
+ =: link "/url" "" "foo"
+ =?> "[[/url][foo]]"
+ , "internal link to anchor"
+ =: link "#my-custom-id" "" "#my-custom-id"
+ =?> "[[#my-custom-id]]"
+ ]
+ ]
diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs
new file mode 100644
index 000000000..ab09bca26
--- /dev/null
+++ b/test/Tests/Writers/Plain.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Plain (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writePlain def) . toPandoc)
+
+
+tests :: [TestTree]
+tests = [ "strongly emphasized text to uppercase"
+ =: strong "Straße"
+ =?> "STRASSE"
+ ]
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
new file mode 100644
index 000000000..9af8fc471
--- /dev/null
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -0,0 +1,93 @@
+module Tests.Writers.Powerpoint (tests) where
+
+import Tests.Writers.OOXML (ooxmlTest)
+import Text.Pandoc
+import Test.Tasty
+import System.FilePath
+
+-- templating is important enough, and can break enough things, that
+-- we want to run all our tests with both default formatting and a
+-- template.
+
+modifyPptxName :: FilePath -> FilePath
+modifyPptxName fp =
+ addExtension (dropExtension fp ++ "_templated") "pptx"
+
+pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree)
+pptxTests name opts native pptx =
+ let referenceDoc = "pptx/reference_depth.pptx"
+ in
+ ( ooxmlTest
+ writePowerpoint
+ name
+ opts{writerReferenceDoc=Nothing}
+ native
+ pptx
+ , ooxmlTest
+ writePowerpoint
+ name
+ opts{writerReferenceDoc=Just referenceDoc}
+ native
+ (modifyPptxName pptx)
+ )
+
+groupPptxTests :: [(TestTree, TestTree)] -> [TestTree]
+groupPptxTests pairs =
+ let (noRefs, refs) = unzip pairs
+ in
+ [ testGroup "Default slide formatting" noRefs
+ , testGroup "With `--reference-doc` pptx file" refs
+ ]
+
+
+tests :: [TestTree]
+tests = groupPptxTests [ pptxTests "Inline formatting"
+ def
+ "pptx/inline_formatting.native"
+ "pptx/inline_formatting.pptx"
+ , pptxTests "Slide breaks (default slide-level)"
+ def
+ "pptx/slide_breaks.native"
+ "pptx/slide_breaks.pptx"
+ , pptxTests "slide breaks (slide-level set to 1)"
+ def{ writerSlideLevel = Just 1 }
+ "pptx/slide_breaks.native"
+ "pptx/slide_breaks_slide_level_1.pptx"
+ , pptxTests "lists"
+ def
+ "pptx/lists.native"
+ "pptx/lists.pptx"
+ , pptxTests "tables"
+ def
+ "pptx/tables.native"
+ "pptx/tables.pptx"
+ , pptxTests "table of contents"
+ def{ writerTableOfContents = True }
+ "pptx/slide_breaks.native"
+ "pptx/slide_breaks_toc.pptx"
+ , pptxTests "end notes"
+ def
+ "pptx/endnotes.native"
+ "pptx/endnotes.pptx"
+ , pptxTests "end notes, with table of contents"
+ def { writerTableOfContents = True }
+ "pptx/endnotes.native"
+ "pptx/endnotes_toc.pptx"
+ , pptxTests "images"
+ def
+ "pptx/images.native"
+ "pptx/images.pptx"
+ , pptxTests "two-column layout"
+ def
+ "pptx/two_column.native"
+ "pptx/two_column.pptx"
+ , pptxTests "speaker notes"
+ def
+ "pptx/speaker_notes.native"
+ "pptx/speaker_notes.pptx"
+ , pptxTests "remove empty slides"
+ def
+ "pptx/remove_empty_slides.native"
+ "pptx/remove_empty_slides.pptx"
+
+ ]
diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs
new file mode 100644
index 000000000..4c0a926bb
--- /dev/null
+++ b/test/Tests/Writers/RST.hs
@@ -0,0 +1,117 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.RST (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeRST def . toPandoc))
+
+tests :: [TestTree]
+tests = [ testGroup "rubrics"
+ [ "in list item" =:
+ bulletList [header 2 (text "foo")] =?>
+ "- .. rubric:: foo"
+ , "in definition list item" =:
+ definitionList [(text "foo", [header 2 (text "bar"),
+ para $ text "baz"])] =?>
+ unlines
+ [ "foo"
+ , " .. rubric:: bar"
+ , ""
+ , " baz"]
+ , "in block quote" =:
+ blockQuote (header 1 (text "bar")) =?>
+ " .. rubric:: bar"
+ , "with id" =:
+ blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?>
+ unlines
+ [ " .. rubric:: bar"
+ , " :name: foo"]
+ , "with id class" =:
+ blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?>
+ unlines
+ [ " .. rubric:: bar"
+ , " :name: foo"
+ , " :class: baz"]
+ ]
+ , testGroup "ligatures" -- handling specific sequences of blocks
+ [ "a list is closed by a comment before a quote" =: -- issue 4248
+ bulletList [plain "bulleted"] <> blockQuote (plain "quoted") =?>
+ unlines
+ [ "- bulleted"
+ , ""
+ , ".."
+ , ""
+ , " quoted"]
+ ]
+ , testGroup "headings"
+ [ "normal heading" =:
+ header 1 (text "foo") =?>
+ unlines
+ [ "foo"
+ , "==="]
+ -- note: heading normalization is only done in standalone mode
+ , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc)
+ "heading levels" $
+ header 1 (text "Header 1") <>
+ header 3 (text "Header 2") <>
+ header 2 (text "Header 2") <>
+ header 1 (text "Header 1") <>
+ header 4 (text "Header 2") <>
+ header 5 (text "Header 3") <>
+ header 3 (text "Header 2") =?>
+ unlines
+ [ "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 3"
+ , "~~~~~~~~"
+ , ""
+ , "Header 2"
+ , "--------"]
+ , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc)
+ "minimal heading levels" $
+ header 2 (text "Header 1") <>
+ header 3 (text "Header 2") <>
+ header 2 (text "Header 1") <>
+ header 4 (text "Header 2") <>
+ header 5 (text "Header 3") <>
+ header 3 (text "Header 2") =?>
+ unlines
+ [ "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 1"
+ , "========"
+ , ""
+ , "Header 2"
+ , "--------"
+ , ""
+ , "Header 3"
+ , "~~~~~~~~"
+ , ""
+ , "Header 2"
+ , "--------"]
+ ]
+ ]
diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs
new file mode 100644
index 000000000..fa372909f
--- /dev/null
+++ b/test/Tests/Writers/TEI.hs
@@ -0,0 +1,43 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.TEI (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+{-
+ "my test" =: X =?> Y
+
+is shorthand for
+
+ test html "my test" $ X =?> Y
+
+which is in turn shorthand for
+
+ test html "my test" (X,Y)
+-}
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+(=:) = test (purely (writeTEI def) . toPandoc)
+
+tests :: [TestTree]
+tests = [ testGroup "block elements"
+ ["para" =: para "Lorem ipsum cetera."
+ =?> "<p>Lorem ipsum cetera.</p>"
+ ]
+ , testGroup "inlines"
+ [
+ "Emphasis" =: emph "emphasized"
+ =?> "<p><hi rendition=\"simple:italic\">emphasized</hi></p>"
+ ,"SingleQuoted" =: singleQuoted (text "quoted material")
+ =?> "<p><quote>quoted material</quote></p>"
+ ,"DoubleQuoted" =: doubleQuoted (text "quoted material")
+ =?> "<p><quote>quoted material</quote></p>"
+ ,"NestedQuoted" =: doubleQuoted (singleQuoted (text "quoted material"))
+ =?> "<p><quote><quote>quoted material</quote></quote></p>"
+ ]
+ ]