diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-01-29 22:13:03 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-29 22:13:03 +0100 |
commit | ae8ac926a43ed48316081b7272701fba3884dbf5 (patch) | |
tree | b6ee822b1d520c0b0690332a0ba3bb253c1a3482 /tests | |
parent | 661f1adedb468314850d0157393b66510a367e28 (diff) | |
parent | a62550f46eeb5f1228548beac9aed43ce2b1f21a (diff) | |
download | pandoc-ae8ac926a43ed48316081b7272701fba3884dbf5.tar.gz |
Merge branch 'typeclass'
Diffstat (limited to 'tests')
56 files changed, 1022 insertions, 310 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs index 69f40fe48..84c2394bc 100644 --- a/tests/Tests/Helpers.hs +++ b/tests/Tests/Helpers.hs @@ -3,6 +3,7 @@ module Tests.Helpers ( test , (=?>) + , purely , property , ToString(..) , ToPandoc(..) @@ -11,11 +12,12 @@ module Tests.Helpers ( test import Text.Pandoc.Definition import Text.Pandoc.Builder (Inlines, Blocks, doc, plain) +import Text.Pandoc.Class import Test.Framework import Test.Framework.Providers.HUnit import Test.Framework.Providers.QuickCheck2 import Test.HUnit (assertBool) -import Text.Pandoc.Shared (normalize, trimr) +import Text.Pandoc.Shared (trimr) import Text.Pandoc.Options import Text.Pandoc.Writers.Native (writeNative) import qualified Test.QuickCheck.Property as QP @@ -49,6 +51,9 @@ vividize (Second s) = "+ " ++ s property :: QP.Testable a => TestName -> a -> Test property = testProperty +purely :: (b -> PandocPure a) -> b -> a +purely f = either (error . show) id . runPure . f + infix 5 =?> (=?>) :: a -> b -> (a,b) x =?> y = (x, y) @@ -57,17 +62,17 @@ class ToString a where toString :: a -> String instance ToString Pandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = 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 = writeNative def . toPandoc + toString = purely (writeNative def) . toPandoc instance ToString Inlines where - toString = trimr . writeNative def . toPandoc + toString = trimr . purely (writeNative def) . toPandoc instance ToString String where toString = id @@ -76,10 +81,10 @@ class ToPandoc a where toPandoc :: a -> Pandoc instance ToPandoc Pandoc where - toPandoc = normalize + toPandoc = id instance ToPandoc Blocks where - toPandoc = normalize . doc + toPandoc = doc instance ToPandoc Inlines where - toPandoc = normalize . doc . plain + toPandoc = doc . plain diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index ef21990ba..f22636747 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -11,15 +11,10 @@ import System.FilePath ( (</>), (<.>), takeDirectory, splitDirectories, import System.Directory import System.Exit import Data.Algorithm.Diff -import Text.Pandoc.Shared ( normalize ) -import Text.Pandoc.Options -import Text.Pandoc.Writers.Native ( writeNative ) -import Text.Pandoc.Readers.Native ( readNative ) import Prelude hiding ( readFile ) import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 (toStringLazy) import Text.Printf -import Text.Pandoc.Error readFileUTF8 :: FilePath -> IO String readFileUTF8 f = B.readFile f >>= return . toStringLazy @@ -52,13 +47,13 @@ tests = [ testGroup "markdown" [ testGroup "writer" $ writerTests "markdown" ++ lhsWriterTests "markdown" , testGroup "reader" - [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] + [ 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", "-S"] + , test "more" ["-r", "markdown", "-w", "native", "-s"] "markdown-reader-more.txt" "markdown-reader-more.native" , lhsReaderTest "markdown+lhs" ] @@ -70,8 +65,8 @@ tests = [ testGroup "markdown" , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") , testGroup "reader" - [ test "basic" ["-r", "rst", "-w", "native", - "-s", "-S", "--columns=80"] "rst-reader.rst" "rst-reader.native" + [ 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" @@ -86,16 +81,17 @@ tests = [ testGroup "markdown" ] ] , testGroup "html" - [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "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" [] "html" + , s5WriterTest "fragment" [] "html4" , s5WriterTest "inserts" ["-s", "-H", "insert", - "-B", "insert", "-A", "insert", "-c", "main.css"] "html" + "-B", "insert", "-A", "insert", "-c", "main.css"] "html4" ] , testGroup "textile" [ testGroup "writer" $ writerTests "textile" @@ -103,7 +99,7 @@ tests = [ testGroup "markdown" "textile-reader.textile" "textile-reader.native" ] , testGroup "docbook" - [ testGroup "writer" $ writerTests "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"] @@ -193,10 +189,9 @@ lhsWriterTests format lhsReaderTest :: String -> Test lhsReaderTest format = - testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] + test "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm - where normalizer = writeNative def . normalize . handleError . readNative - norm = if format == "markdown+lhs" + where norm = if format == "markdown+lhs" then "lhs-test-markdown.native" else "lhs-test.native" @@ -259,7 +254,7 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm - let options = ["--data-dir", ".." </> "data"] ++ [inpPath] ++ opts + let options = ["--quiet", "--data-dir", ".." </> "data"] ++ [inpPath] ++ opts let cmd = pandocPath ++ " " ++ unwords options let findDynlibDir [] = Nothing findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 0d31eb629..8ced43907 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -1,19 +1,17 @@ module Tests.Readers.Docx (tests) where -import Text.Pandoc.Options -import Text.Pandoc.Readers.Native -import Text.Pandoc.Definition +import Text.Pandoc import Tests.Helpers import Test.Framework import Test.HUnit (assertBool) import Test.Framework.Providers.HUnit import qualified Data.ByteString.Lazy as B -import Text.Pandoc.Readers.Docx import Text.Pandoc.Writers.Native (writeNative) import qualified Data.Map as M import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory) import Codec.Archive.Zip -import Text.Pandoc.Error +import Text.Pandoc.Class (runIOorExplode) +import qualified Text.Pandoc.Class as P -- We define a wrapper around pandoc that doesn't normalize in the -- tests. Since we do our own normalization, we want to make sure @@ -25,8 +23,11 @@ data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} noNorm :: Pandoc -> NoNormPandoc noNorm = NoNormPandoc +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "docx" } + instance ToString NoNormPandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing @@ -42,8 +43,9 @@ compareOutput :: ReaderOptions compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile - let (p, _) = handleError $ readDocx opts df - return $ (noNorm p, noNorm (handleError $ readNative nf)) + p <- runIOorExplode $ readDocx opts df + df' <- runIOorExplode $ readNative def nf + return $ (noNorm p, noNorm df') testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do @@ -55,12 +57,13 @@ testCompareWithOpts opts name docxFile nativeFile = buildTest $ testCompareWithOptsIO opts name docxFile nativeFile testCompare :: String -> FilePath -> FilePath -> Test -testCompare = testCompareWithOpts def +testCompare = testCompareWithOpts defopts testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test testForWarningsWithOptsIO opts name docxFile expected = do df <- B.readFile docxFile - let (_, _, warns) = handleError $ readDocxWithWarnings opts df + logs <- runIOorExplode (readDocx opts df >> P.getLog) + let warns = [s | (WARNING, s) <- logs] return $ test id name (unlines warns, unlines expected) testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> Test @@ -68,7 +71,7 @@ testForWarningsWithOpts opts name docxFile expected = buildTest $ testForWarningsWithOptsIO opts name docxFile expected -- testForWarnings :: String -> FilePath -> [String] -> Test --- testForWarnings = testForWarningsWithOpts def +-- testForWarnings = testForWarningsWithOpts defopts getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString) getMedia archivePath mediaPath = do @@ -93,7 +96,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do compareMediaBagIO :: FilePath -> IO Bool compareMediaBagIO docxFile = do df <- B.readFile docxFile - let (_, mb) = handleError $ readDocx def df + mb <- runIOorExplode (readDocx defopts df >> P.getMediaBag) bools <- mapM (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) (mediaDirectory mb) diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs index 2ad36eba6..9190671c3 100644 --- a/tests/Tests/Readers/EPUB.hs +++ b/tests/Tests/Readers/EPUB.hs @@ -7,10 +7,12 @@ import Test.Framework.Providers.HUnit import qualified Data.ByteString.Lazy as BL import Text.Pandoc.Readers.EPUB import Text.Pandoc.MediaBag (MediaBag, mediaDirectory) -import Text.Pandoc.Error +import qualified Text.Pandoc.Class as P getMediaBag :: FilePath -> IO MediaBag -getMediaBag fp = snd . handleError . readEPUB def <$> BL.readFile fp +getMediaBag fp = do + bs <- BL.readFile fp + snd <$> (P.runIOorExplode $ P.withMediaBag $ readEPUB def bs) testMediaBag :: FilePath -> [(String, String, Int)] -> IO () testMediaBag fp bag = do diff --git a/tests/Tests/Readers/HTML.hs b/tests/Tests/Readers/HTML.hs index 1426a8bea..a1533e42a 100644 --- a/tests/Tests/Readers/HTML.hs +++ b/tests/Tests/Readers/HTML.hs @@ -9,7 +9,7 @@ import Text.Pandoc.Builder import Text.Pandoc html :: String -> Pandoc -html = handleError . readHtml def +html = purely $ readHtml def tests :: [Test] tests = [ testGroup "base tag" diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 27e775724..d8572b15b 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -9,7 +9,8 @@ import Text.Pandoc.Builder import Text.Pandoc latex :: String -> Pandoc -latex = handleError . readLaTeX def +latex = purely $ readLaTeX def{ + readerExtensions = getDefaultExtensions "latex" } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 439307dc9..65edf7c38 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -6,21 +6,23 @@ import Test.Framework import Tests.Helpers import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder -import qualified Data.Set as Set import Text.Pandoc markdown :: String -> Pandoc -markdown = handleError . readMarkdown def +markdown = purely $ readMarkdown def { readerExtensions = + disableExtension Ext_smart pandocExtensions } markdownSmart :: String -> Pandoc -markdownSmart = handleError . readMarkdown def { readerSmart = True } +markdownSmart = purely $ readMarkdown def { readerExtensions = + enableExtension Ext_smart pandocExtensions } markdownCDL :: String -> Pandoc -markdownCDL = handleError . readMarkdown def { readerExtensions = Set.insert - Ext_compact_definition_lists $ readerExtensions def } +markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension + Ext_compact_definition_lists pandocExtensions } markdownGH :: String -> Pandoc -markdownGH = handleError . readMarkdown def { readerExtensions = githubMarkdownExtensions } +markdownGH = purely $ readMarkdown def { + readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c @@ -29,8 +31,8 @@ infix 4 =: testBareLink :: (String, Inlines) -> Test testBareLink (inp, ils) = - test (handleError . readMarkdown def{ readerExtensions = - Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] }) + test (purely $ readMarkdown def{ readerExtensions = + extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] }) inp (inp, doc $ para ils) autolink :: String -> Inlines @@ -303,8 +305,8 @@ tests = [ testGroup "inline code" =?> para (note (para "See [^1]")) ] , testGroup "lhs" - [ test (handleError . readMarkdown def{ readerExtensions = Set.insert - Ext_literate_haskell $ readerExtensions def }) + [ 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" diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index 56711c76b..63283497b 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -1,17 +1,16 @@ module Tests.Readers.Odt (tests) where import Control.Monad ( liftM ) -import Text.Pandoc.Options -import Text.Pandoc.Readers.Native -import Text.Pandoc.Readers.Markdown -import Text.Pandoc.Definition +import Text.Pandoc +import Text.Pandoc.Class (runIO) import Tests.Helpers import Test.Framework import qualified Data.ByteString.Lazy as B -import Text.Pandoc.Readers.Odt import Text.Pandoc.Writers.Native (writeNative) import qualified Data.Map as M -import Text.Pandoc.Error + +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "odt" } tests :: [Test] tests = testsComparingToMarkdown ++ testsComparingToNative @@ -41,7 +40,7 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} deriving ( Show ) instance ToString NoNormPandoc where - toString d = writeNative def{ writerTemplate = s } $ toPandoc d + toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing @@ -62,16 +61,18 @@ compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do nativeFile <- Prelude.readFile nativePath odtFile <- B.readFile odtPath - let native = getNoNormVia id "native" $ readNative nativeFile - let odt = getNoNormVia fst "odt" $ readOdt opts odtFile + 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 <- Prelude.readFile markdownPath odtFile <- B.readFile odtPath - let markdown = getNoNormVia id "markdown" $ readMarkdown opts markdownFile - let odt = getNoNormVia fst "odt" $ readOdt opts odtFile + markdown <- getNoNormVia id "markdown" <$> + runIO (readMarkdown def{ readerExtensions = pandocExtensions } + markdownFile) + odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,markdown) @@ -80,7 +81,7 @@ createTest :: TestCreator -> FilePath -> FilePath -> Test createTest creator name path1 path2 = - buildTest $ liftM (test id name) (creator def path1 path2) + buildTest $ liftM (test id name) (creator defopts path1 path2) {- -- diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index 72b7e2601..ef0530b37 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -9,10 +9,11 @@ import Text.Pandoc import Data.List (intersperse) org :: String -> Pandoc -org = handleError . readOrg def - +org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } + orgSmart :: String -> Pandoc -orgSmart = handleError . readOrg def { readerSmart = True } +orgSmart = purely $ readOrg def { readerExtensions = + enableExtension Ext_smart $ getDefaultExtensions "org" } infix 4 =: (=:) :: ToString c @@ -1525,7 +1526,7 @@ tests = , "" , "#+RESULTS:" , ": 65" ] =?> - rawBlock "html" "" + (mempty :: Blocks) , "Source block with toggling header arguments" =: unlines [ "#+BEGIN_SRC sh :noeval" diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs index 9ecbb7af7..464720496 100644 --- a/tests/Tests/Readers/RST.hs +++ b/tests/Tests/Readers/RST.hs @@ -9,7 +9,7 @@ import Text.Pandoc.Builder import Text.Pandoc rst :: String -> Pandoc -rst = handleError . readRST def{ readerStandalone = True } +rst = purely $ readRST def{ readerStandalone = True } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs index 1bda32a49..46831d86f 100644 --- a/tests/Tests/Readers/Txt2Tags.hs +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -8,10 +8,17 @@ import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Data.List (intersperse) -import Text.Pandoc.Readers.Txt2Tags +import Text.Pandoc.Class + t2t :: String -> Pandoc -t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def +-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def +t2t = purely $ \s -> do + putCommonState + def { stInputFiles = Just ["in"] + , stOutputFile = Just "out" + } + readTxt2Tags def s infix 4 =: (=:) :: ToString c @@ -78,10 +85,10 @@ tests = , "Macros: Date" =: "%%date" =?> - para "date" + para "1970-01-01" , "Macros: Mod Time" =: "%%mtime" =?> - para "mtime" + para (str "") , "Macros: Infile" =: "%%infile" =?> para "in" diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs index 55f520433..9b9aeb6a3 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Shared.hs @@ -1,9 +1,7 @@ module Tests.Shared (tests) where -import Text.Pandoc.Definition import Text.Pandoc.Shared import Test.Framework -import Tests.Helpers import Text.Pandoc.Arbitrary() import Test.Framework.Providers.HUnit import Test.HUnit ( assertBool, (@?=) ) @@ -11,33 +9,15 @@ import Text.Pandoc.Builder import System.FilePath.Posix (joinPath) tests :: [Test] -tests = [ testGroup "normalize" - [ property "p_normalize_blocks_rt" p_normalize_blocks_rt - , property "p_normalize_inlines_rt" p_normalize_inlines_rt - , property "p_normalize_no_trailing_spaces" - p_normalize_no_trailing_spaces - ] - , testGroup "compactify'DL" - [ testCase "compactify'DL with empty def" $ - assertBool "compactify'DL" +tests = [ testGroup "compactifyDL" + [ testCase "compactifyDL with empty def" $ + assertBool "compactifyDL" (let x = [(str "word", [para (str "def"), mempty])] - in compactify'DL x == x) + in compactifyDL x == x) ] , testGroup "collapseFilePath" testCollapse ] -p_normalize_blocks_rt :: [Block] -> Bool -p_normalize_blocks_rt bs = - normalizeBlocks bs == normalizeBlocks (normalizeBlocks bs) - -p_normalize_inlines_rt :: [Inline] -> Bool -p_normalize_inlines_rt ils = - normalizeInlines ils == normalizeInlines (normalizeInlines ils) - -p_normalize_no_trailing_spaces :: [Inline] -> Bool -p_normalize_no_trailing_spaces ils = null ils' || last ils' /= Space - where ils' = normalizeInlines $ ils ++ [Space] - testCollapse :: [Test] testCollapse = map (testCase "collapse") [ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""])) diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs deleted file mode 100644 index 876d75e30..000000000 --- a/tests/Tests/Walk.hs +++ /dev/null @@ -1,46 +0,0 @@ -{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-} -module Tests.Walk (tests) where - -import Text.Pandoc.Definition -import Text.Pandoc.Walk -import Test.Framework -import Tests.Helpers -import Data.Char (toUpper) -import Text.Pandoc.Arbitrary() -import Data.Generics - -tests :: [Test] -tests = [ testGroup "Walk" - [ property "p_walk inlineTrans" (p_walk inlineTrans) - , property "p_walk blockTrans" (p_walk blockTrans) - , property "p_query inlineQuery" (p_query inlineQuery) - , property "p_query blockQuery" (p_query blockQuery) - ] - ] - -p_walk :: (Typeable a, Walkable a Pandoc) - => (a -> a) -> Pandoc -> Bool -p_walk f d = everywhere (mkT f) d == walk f d - -p_query :: (Eq a, Typeable a1, Monoid a, Walkable a1 Pandoc) - => (a1 -> a) -> Pandoc -> Bool -p_query f d = everything mappend (mempty `mkQ` f) d == query f d - -inlineTrans :: Inline -> Inline -inlineTrans (Str xs) = Str $ map toUpper xs -inlineTrans (Emph xs) = Strong xs -inlineTrans x = x - -blockTrans :: Block -> Block -blockTrans (Plain xs) = Para xs -blockTrans (BlockQuote xs) = Div ("",["special"],[]) xs -blockTrans x = x - -inlineQuery :: Inline -> String -inlineQuery (Str xs) = xs -inlineQuery _ = "" - -blockQuery :: Block -> [Int] -blockQuery (Header lev _ _) = [lev] -blockQuery _ = [] - diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs index 8ab216753..7103b838b 100644 --- a/tests/Tests/Writers/AsciiDoc.hs +++ b/tests/Tests/Writers/AsciiDoc.hs @@ -7,7 +7,7 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() asciidoc :: (ToPandoc a) => a -> String -asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc +asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc tests :: [Test] tests = [ testGroup "emphasis" diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs index 629e58b8f..b3e12a571 100644 --- a/tests/Tests/Writers/ConTeXt.hs +++ b/tests/Tests/Writers/ConTeXt.hs @@ -8,10 +8,10 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() context :: (ToPandoc a) => a -> String -context = writeConTeXt def . toPandoc +context = purely (writeConTeXt def) . toPandoc context' :: (ToPandoc a) => a -> String -context' = writeConTeXt def{ writerWrapText = WrapNone } . toPandoc +context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs index a288242dc..f34f2495c 100644 --- a/tests/Tests/Writers/Docbook.hs +++ b/tests/Tests/Writers/Docbook.hs @@ -11,7 +11,7 @@ docbook :: (ToPandoc a) => a -> String docbook = docbookWithOpts def{ writerWrapText = WrapNone } docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String -docbookWithOpts opts = writeDocbook opts . toPandoc +docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc {- "my test" =: X =?> Y diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index 31fc3a47b..fd320d224 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -7,8 +7,8 @@ import Tests.Helpers import Test.Framework import Text.Pandoc.Readers.Docx import Text.Pandoc.Writers.Docx -import Text.Pandoc.Error import System.FilePath ((</>)) +import Text.Pandoc.Class (runIOorExplode) type Options = (WriterOptions, ReaderOptions) @@ -20,10 +20,12 @@ compareOutput opts nativeFileIn nativeFileOut = do nf <- Prelude.readFile nativeFileIn nf' <- Prelude.readFile nativeFileOut let wopts = fst opts - df <- writeDocx wopts{writerUserDataDir = Just (".." </> "data")} - (handleError $ readNative nf) - let (p, _) = handleError $ readDocx (snd opts) df - return (p, handleError $ readNative nf') + df <- runIOorExplode $ do + d <- readNative def nf + writeDocx wopts{writerUserDataDir = Just (".." </> "data")} d + df' <- runIOorExplode (readNative def nf') + p <- runIOorExplode $ readDocx (snd opts) df + return (p, df') testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do @@ -139,7 +141,7 @@ tests = [ testGroup "inlines" ] , testGroup "customized styles" [ testCompareWithOpts - ( def{writerReferenceDocx=Just "docx/custom-style-reference.docx"} + ( def{writerReferenceDoc=Just "docx/custom-style-reference.docx"} , def) "simple customized blocks and inlines" "docx/custom-style-roundtrip-start.native" diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs index 5bea99f71..45de2b042 100644 --- a/tests/Tests/Writers/HTML.hs +++ b/tests/Tests/Writers/HTML.hs @@ -8,7 +8,7 @@ import Tests.Helpers import Text.Pandoc.Arbitrary() html :: (ToPandoc a) => a -> String -html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc +html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc {- "my test" =: X =?> Y @@ -31,7 +31,7 @@ tests :: [Test] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "<code>@&</code>" , "haskell" =: codeWith ("",["haskell"],[]) ">>=" - =?> "<code class=\"haskell\">>>=</code>" + =?> "<code class=\"sourceCode haskell\"><span class=\"fu\">>>=</span></code>" , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" =?> "<code class=\"nolanguage\">>>=</code>" ] diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index f140cc2dd..f54aef4dc 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -8,13 +8,16 @@ import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder latex :: (ToPandoc a) => a -> String -latex = latexWithOpts def{ writerHighlight = True } +latex = latexWithOpts def latexListing :: (ToPandoc a) => a -> String latexListing = latexWithOpts def{ writerListings = True } latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -latexWithOpts opts = writeLaTeX opts . toPandoc +latexWithOpts opts = purely (writeLaTeX opts) . toPandoc + +beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +beamerWithOpts opts = purely (writeBeamer opts) . toPandoc {- "my test" =: X =?> Y @@ -95,8 +98,7 @@ tests = [ testGroup "code blocks" beamerTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String beamerTopLevelDiv division = - latexWithOpts def { writerTopLevelDivision = division - , writerBeamer = True } + beamerWithOpts def { writerTopLevelDivision = division } in [ test (latexTopLevelDiv TopLevelSection) "sections as top-level" $ headers =?> diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index aab916b38..abefe27d5 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -8,11 +8,14 @@ import Text.Pandoc import Tests.Helpers import Text.Pandoc.Arbitrary() +defopts :: WriterOptions +defopts = def{ writerExtensions = pandocExtensions } + markdown :: (ToPandoc a) => a -> String -markdown = writeMarkdown def . toPandoc +markdown = purely (writeMarkdown defopts) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String -markdownWithOpts opts x = writeMarkdown opts $ toPandoc x +markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x {- "my test" =: X =?> Y @@ -84,7 +87,7 @@ noteTestDoc = noteTests :: Test noteTests = testGroup "note and reference location" - [ test (markdownWithOpts def) + [ test (markdownWithOpts defopts) "footnotes at the end of a document" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -105,7 +108,7 @@ noteTests = testGroup "note and reference location" , "" , "[^2]: The second note." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock}) "footnotes at the end of blocks" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -126,7 +129,7 @@ noteTests = testGroup "note and reference location" , "" , "Some more text." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) "footnotes and reference links at the end of blocks" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -149,7 +152,7 @@ noteTests = testGroup "note and reference location" , "" , "Some more text." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfSection}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection}) "footnotes at the end of section" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -179,7 +182,7 @@ shortcutLinkRefsTests = (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test - (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc) + (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc) in testGroup "Shortcut reference links" [ "Simple link (shortcutable)" =: (para (link "/url" "title" "foo")) diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs index 7ec43b339..88bad7944 100644 --- a/tests/Tests/Writers/Native.hs +++ b/tests/Tests/Writers/Native.hs @@ -8,11 +8,11 @@ import Text.Pandoc.Arbitrary() p_write_rt :: Pandoc -> Bool p_write_rt d = - read (writeNative def{ writerTemplate = Just "" } d) == d + read (purely (writeNative def{ writerTemplate = Just "" }) d) == d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = length bs > 20 || - read (writeNative def (Pandoc nullMeta bs)) == + read (purely (writeNative def) (Pandoc nullMeta bs)) == bs tests :: [Test] diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs index 42f77e3ec..bead6857c 100644 --- a/tests/Tests/Writers/Plain.hs +++ b/tests/Tests/Writers/Plain.hs @@ -11,7 +11,7 @@ import Text.Pandoc.Arbitrary() infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writePlain def . toPandoc) +(=:) = test (purely (writePlain def) . toPandoc) tests :: [Test] diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs index 77dafeb4c..dd55580c9 100644 --- a/tests/Tests/Writers/RST.hs +++ b/tests/Tests/Writers/RST.hs @@ -10,7 +10,7 @@ import Text.Pandoc.Arbitrary() infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writeRST def{ writerHighlight = True } . toPandoc) +(=:) = test (purely (writeRST def . toPandoc)) tests :: [Test] tests = [ testGroup "rubrics" @@ -47,7 +47,7 @@ tests = [ testGroup "rubrics" [ "foo" , "==="] -- note: heading normalization is only done in standalone mode - , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) "heading levels" $ header 1 (text "Header 1") <> header 3 (text "Header 2") <> @@ -77,7 +77,7 @@ tests = [ testGroup "rubrics" , "" , "Header 2" , "--------"] - , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) "minimal heading levels" $ header 2 (text "Header 1") <> header 3 (text "Header 2") <> diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs index 3eb8478b7..703f565bb 100644 --- a/tests/Tests/Writers/TEI.hs +++ b/tests/Tests/Writers/TEI.hs @@ -22,7 +22,7 @@ which is in turn shorthand for infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test -(=:) = test (writeTEI def . toPandoc) +(=:) = test (purely (writeTEI def) . toPandoc) tests :: [Test] tests = [ testGroup "block elements" diff --git a/tests/fb2/basic.fb2 b/tests/fb2/basic.fb2 index 14b03fbea..ffb2bfbdf 100644 --- a/tests/fb2/basic.fb2 +++ b/tests/fb2/basic.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Top-level title</p></title><section><title><p>Section</p></title><section><title><p>Subsection</p></title><p>This <emphasis>emphasized</emphasis> <strong>strong</strong> <code>verbatim</code> markdown. See this link<a l:href="#l1" type="note"><sup>[1]</sup></a>.</p><p>Ordered list:</p><p> 1. one</p><p> 2. two</p><p> 3. three</p><cite><p>Blockquote is for citatons.</p></cite><empty-line /><p><code>Code</code></p><p><code>block</code></p><p><code>is</code></p><p><code>for</code></p><p><code>code.</code></p><empty-line /><p><strikethrough>Strikeout</strikethrough> is Pandoc's extension. Superscript and subscripts too: H<sub>2</sub>O is a liquid<a l:href="#n2" type="note"><sup>[2]</sup></a>. 2<sup>10</sup> is 1024.</p><p>Math is another Pandoc extension: <code>E = m c^2</code>.</p></section></section></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>http://example.com/</code></p></section><section id="n2"><title><p>2</p></title><p>Sometimes.</p></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Top-level title</p></title><section><title><p>Section</p></title><section><title><p>Subsection</p></title><p>This <emphasis>emphasized</emphasis> <strong>strong</strong> <code>verbatim</code> markdown. See this link<a l:href="#l1" type="note"><sup>[1]</sup></a>.</p><p>Ordered list:</p><p> 1. one</p><p> 2. two</p><p> 3. three</p><cite><p>Blockquote is for citatons.</p></cite><empty-line /><p><code>Code</code></p><p><code>block</code></p><p><code>is</code></p><p><code>for</code></p><p><code>code.</code></p><empty-line /><p><strikethrough>Strikeout</strikethrough> is Pandoc’s extension. Superscript and subscripts too: H<sub>2</sub>O is a liquid<a l:href="#n2" type="note"><sup>[2]</sup></a>. 2<sup>10</sup> is 1024.</p><p>Math is another Pandoc extension: <code>E = m c^2</code>.</p></section></section></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>http://example.com/</code></p></section><section id="n2"><title><p>2</p></title><p>Sometimes.</p></section></body></FictionBook> + diff --git a/tests/fb2/titles.fb2 b/tests/fb2/titles.fb2 index d8fc1e424..9e8d47e36 100644 --- a/tests/fb2/titles.fb2 +++ b/tests/fb2/titles.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Simple title</p></title><p>This example tests if Pandoc doesn't insert forbidden elements in FictionBook titles.</p></section><section><title><p>Emphasized Strong Title</p></title></section><section><title><p>Title with</p><empty-line /><p>line break</p></title></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Simple title</p></title><p>This example tests if Pandoc doesn’t insert forbidden elements in FictionBook titles.</p></section><section><title><p>Emphasized Strong Title</p></title></section><section><title><p>Title with</p><empty-line /><p>line break</p></title></section></body></FictionBook> + diff --git a/tests/lhs-test.html b/tests/lhs-test.html index e4a5b3868..2c3b6b0f8 100644 --- a/tests/lhs-test.html +++ b/tests/lhs-test.html @@ -1,9 +1,9 @@ -<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml"> +<!DOCTYPE html> +<html> <head> - <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> - <meta http-equiv="Content-Style-Type" content="text/css" /> - <meta name="generator" content="pandoc" /> + <meta charset="utf-8"> + <meta name="generator" content="pandoc"> + <meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes"> <title></title> <style type="text/css">code{white-space: pre;}</style> <style type="text/css"> @@ -43,6 +43,9 @@ code > span.an { color: #60a0b0; font-weight: bold; font-style: italic; } /* Ann code > span.cv { color: #60a0b0; font-weight: bold; font-style: italic; } /* CommentVar */ code > span.in { color: #60a0b0; font-weight: bold; font-style: italic; } /* Information */ </style> + <!--[if lt IE 9]> + <script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script> + <![endif]--> </head> <body> <h1 id="lhs-test">lhs test</h1> diff --git a/tests/lhs-test.html+lhs b/tests/lhs-test.html+lhs index 41e9ca283..443b0642f 100644 --- a/tests/lhs-test.html+lhs +++ b/tests/lhs-test.html+lhs @@ -1,9 +1,9 @@ -<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml"> +<!DOCTYPE html> +<html> <head> - <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> - <meta http-equiv="Content-Style-Type" content="text/css" /> - <meta name="generator" content="pandoc" /> + <meta charset="utf-8"> + <meta name="generator" content="pandoc"> + <meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes"> <title></title> <style type="text/css">code{white-space: pre;}</style> <style type="text/css"> @@ -43,6 +43,9 @@ code > span.an { color: #60a0b0; font-weight: bold; font-style: italic; } /* Ann code > span.cv { color: #60a0b0; font-weight: bold; font-style: italic; } /* CommentVar */ code > span.in { color: #60a0b0; font-weight: bold; font-style: italic; } /* Information */ </style> + <!--[if lt IE 9]> + <script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script> + <![endif]--> </head> <body> <h1 id="lhs-test">lhs test</h1> diff --git a/tests/markdown-citations.native b/tests/markdown-citations.native index d9738fb4f..c77ccbbfc 100644 --- a/tests/markdown-citations.native +++ b/tests/markdown-citations.native @@ -3,15 +3,15 @@ [[Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@nonexistent]"]]] ,[Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@nonexistent"]]] ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30,",Space,Str "with",Space,Str "suffix]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[-@item2",Space,Str "p.",Space,Str "30;",Space,Str "see",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@\1087\1091\1085\1082\1090\&3",Space,Str "[p.",Space,Str "12]"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@\1087\1091\1085\1082\1090\&3]"],Str "."]]]] - ,[Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3",Space,Str "p.",Space,Str "34-35]"],Str "."]] - ,[Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "p.",Space,Str "34-35]"],Str "."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.\160\&30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.\160\&30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30,",Space,Str "with",Space,Str "suffix]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.\160\&30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[-@item2",Space,Str "p.",Space,Str "30;",Space,Str "see",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.\160\&12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@\1087\1091\1085\1082\1090\&3",Space,Str "[p.",Space,Str "12]"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@\1087\1091\1085\1082\1090\&3]"],Str "."]]]] + ,[Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.\160\&34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3",Space,Str "p.",Space,Str "34-35]"],Str "."]] + ,[Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.\160\&34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "p.",Space,Str "34-35]"],Str "."]] ,[Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "@\1087\1091\1085\1082\1090\&3;",Space,Str "@item2]"],Str "."]]]] - ,[Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] + ,[Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.\160\&33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] ,[Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] - ,[Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item1]"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item2",Space,Str "p.",Space,Str "44]"],Str "."]]]] + ,[Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item1]"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.\160\&44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item2",Space,Str "p.",Space,Str "44]"],Str "."]]]] ,[Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[*see*",Space,Str "@item1",Space,Str "p.",Space,Str "**32**]"],Str "."]]] ,Header 1 ("references",[],[]) [Str "References"]] diff --git a/tests/rst-reader.native b/tests/rst-reader.native index 768a05c24..bc4641a3f 100644 --- a/tests/rst-reader.native +++ b/tests/rst-reader.native @@ -327,15 +327,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Some",Space,Superscript [Str "of"],Space,Str "these",Space,Superscript [Str "words"],Space,Str "are",Space,Str "in",Space,Superscript [Str "superscript"],Str "."] ,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."] ,Para [Str "And",Space,Str "now",Space,Str "some-invalid-string-3231231",Space,Str "is",Space,Str "nonsense."] -,Null ,Para [Str "And",Space,Str "now",Space,Str "with",Space,RawInline (Format "html") "<b>inline</b> <span id=\"test\">HTML</span>",Str "."] -,Null ,Para [Str "And",Space,Str "some",Space,Str "inline",Space,Str "haskell",Space,Code ("",["haskell","sourceCode"],[]) "fmap id [1,2..10]",Str "."] -,Null -,Null ,Para [Str "Indirect",Space,Str "python",Space,Str "role",Space,Code ("",["py","python","indirect","sourceCode"],[]) "[x*x for x in [1,2,3,4,5]]",Str "."] -,Null -,Null ,Para [Str "Different",Space,Str "indirect",Space,Str "C",Space,Code ("",["c","different-indirect","sourceCode"],[]) "int x = 15;",Str "."] ,Header 2 ("literal-symbols",[],[]) [Str "Literal",Space,Str "symbols"] ,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]] diff --git a/tests/tables-rstsubset.native b/tests/tables-rstsubset.native index c98a95541..ecf6911dc 100644 --- a/tests/tables-rstsubset.native +++ b/tests/tables-rstsubset.native @@ -67,8 +67,8 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] -,Para [Str "Table:",Space,Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] +,Para [Str "Table:",Space,Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625] [[Plain [Str "Centered",Space,Str "Header"]] @@ -82,7 +82,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,0.1,0.1,0.1] [[] @@ -114,4 +114,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] diff --git a/tests/tables.asciidoc b/tests/tables.asciidoc index 2a24544a3..91490a27a 100644 --- a/tests/tables.asciidoc +++ b/tests/tables.asciidoc @@ -32,12 +32,12 @@ Simple table indented two spaces: Multiline table with caption: -.Here's the caption. It may span multiple lines. +.Here’s the caption. It may span multiple lines. [width="78%",cols="^21%,<17%,>20%,<42%",options="header",] |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= Multiline table without caption: @@ -46,7 +46,7 @@ Multiline table without caption: |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= Table without column headers: @@ -63,5 +63,5 @@ Multiline table without column headers: [width="78%",cols="^21%,<17%,>20%,42%",] |======================================================================= |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= diff --git a/tests/tables.docbook b/tests/tables.docbook4 index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook +++ b/tests/tables.docbook4 @@ -222,7 +222,7 @@ </para> <table> <title> - Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. </title> <tgroup cols="4"> <colspec colwidth="15*" align="center" /> @@ -271,7 +271,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -328,7 +328,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -424,7 +424,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> diff --git a/tests/tables.docbook5 b/tests/tables.docbook5 index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook5 +++ b/tests/tables.docbook5 @@ -222,7 +222,7 @@ </para> <table> <title> - Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. </title> <tgroup cols="4"> <colspec colwidth="15*" align="center" /> @@ -271,7 +271,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -328,7 +328,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -424,7 +424,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> diff --git a/tests/tables.dokuwiki b/tests/tables.dokuwiki index 21e61f656..23c0d22cb 100644 --- a/tests/tables.dokuwiki +++ b/tests/tables.dokuwiki @@ -23,16 +23,16 @@ Demonstration of simple table syntax. Multiline table with caption: -Here's the caption. It may span multiple lines. +Here’s the caption. It may span multiple lines. ^ Centered Header ^Left Aligned ^ Right Aligned^Default aligned ^ | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Multiline table without caption: ^ Centered Header ^Left Aligned ^ Right Aligned^Default aligned ^ | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Table without column headers: @@ -43,5 +43,5 @@ Table without column headers: Multiline table without column headers: | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows.| +| Second |row | 5.0|Here’s another one. Note the blank line between rows.| diff --git a/tests/tables.fb2 b/tests/tables.fb2 index f636e9fd4..df285888e 100644 --- a/tests/tables.fb2 +++ b/tests/tables.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><p>Simple table with caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Simple table without caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis /></p><p>Simple table indented two spaces:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Multiline table with caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis>Here's the caption. It may span multiple lines.</emphasis></p><p>Multiline table without caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><th align="right" /><th align="left" /><th align="center" /><th align="right" /></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><th align="center" /><th align="left" /><th align="right" /><th align="left" /></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><p>Simple table with caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Simple table without caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis /></p><p>Simple table indented two spaces:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Multiline table with caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis>Here’s the caption. It may span multiple lines.</emphasis></p><p>Multiline table without caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><th align="right" /><th align="left" /><th align="center" /><th align="right" /></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><th align="center" /><th align="left" /><th align="right" /><th align="left" /></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p></section></body></FictionBook> + diff --git a/tests/tables.haddock b/tests/tables.haddock index f9efdc0de..84a15cce8 100644 --- a/tests/tables.haddock +++ b/tests/tables.haddock @@ -35,12 +35,12 @@ Multiline table with caption: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > -------------------------------------------------------------- > -> Here\'s the caption. It may span multiple lines. +> Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -51,7 +51,7 @@ Multiline table without caption: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > -------------------------------------------------------------- @@ -70,7 +70,7 @@ Multiline table without column headers: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > ----------- ---------- ------------ -------------------------- diff --git a/tests/tables.html b/tests/tables.html4 index 0a9ea413c..5bb7a7de2 100644 --- a/tests/tables.html +++ b/tests/tables.html4 @@ -95,7 +95,7 @@ </table> <p>Multiline table with caption:</p> <table style="width:79%;"> -<caption>Here's the caption. It may span multiple lines.</caption> +<caption>Here’s the caption. It may span multiple lines.</caption> <colgroup> <col width="15%" /> <col width="13%" /> @@ -121,7 +121,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> +<td align="left">Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> @@ -152,7 +152,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> +<td align="left">Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> @@ -198,7 +198,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td>Here's another one. Note the blank line between rows.</td> +<td>Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> diff --git a/tests/tables.html5 b/tests/tables.html5 new file mode 100644 index 000000000..17a82110f --- /dev/null +++ b/tests/tables.html5 @@ -0,0 +1,204 @@ +<p>Simple table with caption:</p> +<table> +<caption>Demonstration of simple table syntax.</caption> +<thead> +<tr class="header"> +<th style="text-align: right;">Right</th> +<th style="text-align: left;">Left</th> +<th style="text-align: center;">Center</th> +<th>Default</th> +</tr> +</thead> +<tbody> +<tr class="odd"> +<td style="text-align: right;">12</td> +<td style="text-align: left;">12</td> +<td style="text-align: center;">12</td> +<td>12</td> +</tr> +<tr class="even"> +<td style="text-align: right;">123</td> +<td style="text-align: left;">123</td> +<td style="text-align: center;">123</td> +<td>123</td> +</tr> +<tr class="odd"> +<td style="text-align: right;">1</td> +<td style="text-align: left;">1</td> +<td style="text-align: center;">1</td> +<td>1</td> +</tr> +</tbody> +</table> +<p>Simple table without caption:</p> +<table> +<thead> +<tr class="header"> +<th style="text-align: right;">Right</th> +<th style="text-align: left;">Left</th> +<th style="text-align: center;">Center</th> +<th>Default</th> +</tr> +</thead> +<tbody> +<tr class="odd"> +<td style="text-align: right;">12</td> +<td style="text-align: left;">12</td> +<td style="text-align: center;">12</td> +<td>12</td> +</tr> +<tr class="even"> +<td style="text-align: right;">123</td> +<td style="text-align: left;">123</td> +<td style="text-align: center;">123</td> +<td>123</td> +</tr> +<tr class="odd"> +<td style="text-align: right;">1</td> +<td style="text-align: left;">1</td> +<td style="text-align: center;">1</td> +<td>1</td> +</tr> +</tbody> +</table> +<p>Simple table indented two spaces:</p> +<table> +<caption>Demonstration of simple table syntax.</caption> +<thead> +<tr class="header"> +<th style="text-align: right;">Right</th> +<th style="text-align: left;">Left</th> +<th style="text-align: center;">Center</th> +<th>Default</th> +</tr> +</thead> +<tbody> +<tr class="odd"> +<td style="text-align: right;">12</td> +<td style="text-align: left;">12</td> +<td style="text-align: center;">12</td> +<td>12</td> +</tr> +<tr class="even"> +<td style="text-align: right;">123</td> +<td style="text-align: left;">123</td> +<td style="text-align: center;">123</td> +<td>123</td> +</tr> +<tr class="odd"> +<td style="text-align: right;">1</td> +<td style="text-align: left;">1</td> +<td style="text-align: center;">1</td> +<td>1</td> +</tr> +</tbody> +</table> +<p>Multiline table with caption:</p> +<table style="width:79%;"> +<caption>Here’s the caption. It may span multiple lines.</caption> +<colgroup> +<col style="width: 15%" /> +<col style="width: 13%" /> +<col style="width: 16%" /> +<col style="width: 33%" /> +</colgroup> +<thead> +<tr class="header"> +<th style="text-align: center;">Centered Header</th> +<th style="text-align: left;">Left Aligned</th> +<th style="text-align: right;">Right Aligned</th> +<th style="text-align: left;">Default aligned</th> +</tr> +</thead> +<tbody> +<tr class="odd"> +<td style="text-align: center;">First</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">12.0</td> +<td style="text-align: left;">Example of a row that spans multiple lines.</td> +</tr> +<tr class="even"> +<td style="text-align: center;">Second</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">5.0</td> +<td style="text-align: left;">Here’s another one. Note the blank line between rows.</td> +</tr> +</tbody> +</table> +<p>Multiline table without caption:</p> +<table style="width:79%;"> +<colgroup> +<col style="width: 15%" /> +<col style="width: 13%" /> +<col style="width: 16%" /> +<col style="width: 33%" /> +</colgroup> +<thead> +<tr class="header"> +<th style="text-align: center;">Centered Header</th> +<th style="text-align: left;">Left Aligned</th> +<th style="text-align: right;">Right Aligned</th> +<th style="text-align: left;">Default aligned</th> +</tr> +</thead> +<tbody> +<tr class="odd"> +<td style="text-align: center;">First</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">12.0</td> +<td style="text-align: left;">Example of a row that spans multiple lines.</td> +</tr> +<tr class="even"> +<td style="text-align: center;">Second</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">5.0</td> +<td style="text-align: left;">Here’s another one. Note the blank line between rows.</td> +</tr> +</tbody> +</table> +<p>Table without column headers:</p> +<table> +<tbody> +<tr class="odd"> +<td style="text-align: right;">12</td> +<td style="text-align: left;">12</td> +<td style="text-align: center;">12</td> +<td style="text-align: right;">12</td> +</tr> +<tr class="even"> +<td style="text-align: right;">123</td> +<td style="text-align: left;">123</td> +<td style="text-align: center;">123</td> +<td style="text-align: right;">123</td> +</tr> +<tr class="odd"> +<td style="text-align: right;">1</td> +<td style="text-align: left;">1</td> +<td style="text-align: center;">1</td> +<td style="text-align: right;">1</td> +</tr> +</tbody> +</table> +<p>Multiline table without column headers:</p> +<table style="width:79%;"> +<colgroup> +<col style="width: 15%" /> +<col style="width: 13%" /> +<col style="width: 16%" /> +<col style="width: 33%" /> +</colgroup> +<tbody> +<tr class="odd"> +<td style="text-align: center;">First</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">12.0</td> +<td>Example of a row that spans multiple lines.</td> +</tr> +<tr class="even"> +<td style="text-align: center;">Second</td> +<td style="text-align: left;">row</td> +<td style="text-align: right;">5.0</td> +<td>Here’s another one. Note the blank line between rows.</td> +</tr> +</tbody> +</table> diff --git a/tests/tables.icml b/tests/tables.icml index 8ce645a2f..0280cafed 100644 --- a/tests/tables.icml +++ b/tests/tables.icml @@ -476,14 +476,14 @@ <Cell Name="3:2" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar > LeftAlign"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> </Table> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TableCaption"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's the caption. It may span multiple lines.</Content> + <Content>Here’s the caption. It may span multiple lines.</Content> </CharacterStyleRange> </ParagraphStyleRange> <Br /> @@ -578,7 +578,7 @@ <Cell Name="3:2" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar > LeftAlign"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> @@ -748,10 +748,10 @@ <Cell Name="3:1" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> </Table> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TableCaption"> -</ParagraphStyleRange>
\ No newline at end of file +</ParagraphStyleRange> diff --git a/tests/tables.man b/tests/tables.man index 788b2199d..dd6a3cce9 100644 --- a/tests/tables.man +++ b/tests/tables.man @@ -135,7 +135,7 @@ T} .PP Multiline table with caption: .PP -Here\[aq]s the caption. It may span multiple lines. +Here's the caption. It may span multiple lines. .TS tab(@); cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). @@ -165,7 +165,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE @@ -201,7 +201,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE @@ -261,7 +261,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE diff --git a/tests/tables.mediawiki b/tests/tables.mediawiki index 614c3eea1..ce7c17887 100644 --- a/tests/tables.mediawiki +++ b/tests/tables.mediawiki @@ -75,7 +75,7 @@ Simple table indented two spaces: Multiline table with caption: {| -|+ Here's the caption. It may span multiple lines. +|+ Here’s the caption. It may span multiple lines. !align="center" width="15%"| Centered Header !width="13%"| Left Aligned !align="right" width="16%"| Right Aligned @@ -89,7 +89,7 @@ Multiline table with caption: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} Multiline table without caption: @@ -108,7 +108,7 @@ Multiline table without caption: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} Table without column headers: @@ -141,6 +141,6 @@ Multiline table without column headers: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} diff --git a/tests/tables.native b/tests/tables.native index a7f4fdcf1..a60f9b586 100644 --- a/tests/tables.native +++ b/tests/tables.native @@ -53,7 +53,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here's",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] +,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -65,7 +65,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] ,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] @@ -79,7 +79,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] [[] @@ -111,4 +111,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] diff --git a/tests/tables.opendocument b/tests/tables.opendocument index 0765bb783..c331ecc43 100644 --- a/tests/tables.opendocument +++ b/tests/tables.opendocument @@ -246,12 +246,12 @@ caption:</text:p> <text:p text:style-name="P16">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table4.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> </table:table> -<text:p text:style-name="Table">Here's the caption. It may span multiple +<text:p text:style-name="Table">Here’s the caption. It may span multiple lines.</text:p> <text:p text:style-name="First_20_paragraph">Multiline table without caption:</text:p> @@ -302,7 +302,7 @@ caption:</text:p> <text:p text:style-name="P20">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table5.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> @@ -390,7 +390,7 @@ headers:</text:p> <text:p text:style-name="P30">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table7.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> diff --git a/tests/tables.plain b/tests/tables.plain index 4b5754cf9..4c7ebbf82 100644 --- a/tests/tables.plain +++ b/tests/tables.plain @@ -35,12 +35,12 @@ Multiline table with caption: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. -------------------------------------------------------------- - : Here's the caption. It may span multiple lines. + : Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -51,7 +51,7 @@ Multiline table without caption: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. -------------------------------------------------------------- @@ -70,7 +70,7 @@ Multiline table without column headers: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. ----------- ---------- ------------ -------------------------- diff --git a/tests/tables.rst b/tests/tables.rst index 25d5932ea..fc7f0b475 100644 --- a/tests/tables.rst +++ b/tests/tables.rst @@ -47,12 +47,12 @@ Multiline table with caption: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ -Table: Here's the caption. It may span multiple lines. +Table: Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -63,7 +63,7 @@ Multiline table without caption: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ @@ -84,7 +84,7 @@ Multiline table without column headers: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ diff --git a/tests/tables.rtf b/tests/tables.rtf index e1fe4aab1..57030b114 100644 --- a/tests/tables.rtf +++ b/tests/tables.rtf @@ -226,11 +226,11 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} -{\pard \ql \f0 \sa180 \li0 \fi0 Here's the caption. It may span multiple lines.\par} +{\pard \ql \f0 \sa180 \li0 \fi0 Here\u8217's the caption. It may span multiple lines.\par} {\pard \ql \f0 \sa180 \li0 \fi0 Multiline table without caption:\par} { \trowd \trgaph120 @@ -273,7 +273,7 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} @@ -352,8 +352,9 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} {\pard \ql \f0 \sa180 \li0 \fi0 \par} + diff --git a/tests/tables.tei b/tests/tables.tei index 45b88b1cb..64438e520 100644 --- a/tests/tables.tei +++ b/tests/tables.tei @@ -97,7 +97,7 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> <p>Multiline table without caption:</p> @@ -118,7 +118,7 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> <p>Table without column headers:</p> @@ -166,6 +166,6 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> diff --git a/tests/tables.zimwiki b/tests/tables.zimwiki index 1f02c9908..6da1f7f2c 100644 --- a/tests/tables.zimwiki +++ b/tests/tables.zimwiki @@ -26,18 +26,18 @@ Demonstration of simple table syntax. Multiline table with caption: -Here's the caption. It may span multiple lines. +Here’s the caption. It may span multiple lines. | Centered Header |Left Aligned | Right Aligned|Default aligned | |:-----------------:|:-------------|--------------:|:------------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Multiline table without caption: | Centered Header |Left Aligned | Right Aligned|Default aligned | |:-----------------:|:-------------|--------------:|:------------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Table without column headers: @@ -52,5 +52,5 @@ Multiline table without column headers: | First |row | 12.0|Example of a row that spans multiple lines. | |:--------:|:----|-----:|-----------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows.| +| Second |row | 5.0|Here’s another one. Note the blank line between rows.| diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 2488917cb..7d0542bf4 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -26,14 +26,12 @@ import qualified Tests.Writers.Docx import qualified Tests.Writers.RST import qualified Tests.Writers.TEI import qualified Tests.Shared -import qualified Tests.Walk import Text.Pandoc.Shared (inDirectory) import System.Environment (getArgs) tests :: [Test] tests = [ testGroup "Old" Tests.Old.tests , testGroup "Shared" Tests.Shared.tests - , testGroup "Walk" Tests.Walk.tests , testGroup "Writers" [ testGroup "Native" Tests.Writers.Native.tests , testGroup "ConTeXt" Tests.Writers.ConTeXt.tests diff --git a/tests/textile-reader.native b/tests/textile-reader.native index c617a53f5..8b3100ffa 100644 --- a/tests/textile-reader.native +++ b/tests/textile-reader.native @@ -1,5 +1,5 @@ Pandoc (Meta {unMeta = fromList []}) -[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."] +[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] ,HorizontalRule ,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 2 ("level-2-with-an-embeded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embeded",Space,Str "link"] ("http://www.example.com","")] @@ -8,9 +8,9 @@ Pandoc (Meta {unMeta = fromList []}) ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 6 ("level-6",[],[]) [Str "Level",Space,Str "6"] ,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"] -,Para [Str "Here's",Space,Str "a",Space,Str "regular",Space,Str "paragraph."] +,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."] ,Para [Str "Line",Space,Str "breaks",Space,Str "are",Space,Str "preserved",Space,Str "in",Space,Str "textile,",Space,Str "so",Space,Str "you",Space,Str "can",Space,Str "not",Space,Str "wrap",Space,Str "your",Space,Str "very",LineBreak,Str "long",Space,Str "paragraph",Space,Str "with",Space,Str "your",Space,Str "favourite",Space,Str "text",Space,Str "editor",Space,Str "and",Space,Str "have",Space,Str "it",Space,Str "rendered",LineBreak,Str "with",Space,Str "no",Space,Str "break."] -,Para [Str "Here's",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet."] +,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet."] ,BulletList [[Plain [Str "criminey."]]] ,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "paragraph",Space,Str "break",Space,Str "between",Space,Str "here"] @@ -89,14 +89,14 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link ("",[],[]) [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."] ,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]] ,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Space,Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts:",Space,Subscript [Str "here"],Space,Str "H",Space,Subscript [Str "2"],Str "O,",Space,Str "H",Space,Subscript [Str "23"],Str "O,",Space,Str "H",Space,Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."] -,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "--",Space,Str "automatic",Space,Str "dashes."] -,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "...",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more."] -,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Str "\"I'd",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you\"",Space,Str "for",Space,Str "example."] +,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes."] +,Para [Str "Elipses",Space,Str ":",Space,Str "He",Space,Str "thought",Space,Str "and",Space,Str "thought",Space,Str "\8230",Space,Str "and",Space,Str "then",Space,Str "thought",Space,Str "some",Space,Str "more."] +,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Quoted DoubleQuote [Str "I\8217d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example."] ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "url"] ("http://www.url.com","")] ,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] -,Para [Str "\"not",Space,Str "a",Space,Str "link\":",Space,Str "foo"] +,Para [Quoted DoubleQuote [Str "not",Space,Str "a",Space,Str "link"],Str ":",Space,Str "foo"] ,Para [Str "Automatic",Space,Str "linking",Space,Str "to",Space,Link ("",[],[]) [Str "http://www.example.com"] ("http://www.example.com",""),Str "."] ,Para [Link ("",[],[]) [Str "Example"] ("http://www.example.com/",""),Str ":",Space,Str "Example",Space,Str "of",Space,Str "a",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "colon."] ,Para [Str "A",Space,Str "link",Link ("",[],[]) [Str "with",Space,Str "brackets"] ("http://www.example.com",""),Str "and",Space,Str "no",Space,Str "spaces."] @@ -117,7 +117,7 @@ Pandoc (Meta {unMeta = fromList []}) ,[[Plain [Str "bella"]] ,[Plain [Str "45"]] ,[Plain [Str "f"]]]] -,Para [Str "and",Space,Str "some",Space,Str "text",Space,Str "following",Space,Str "..."] +,Para [Str "and",Space,Str "some",Space,Str "text",Space,Str "following",Space,Str "\8230"] ,Header 2 ("with-headers",[],[]) [Str "With",Space,Str "headers"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] [[Plain [Str "name"]] diff --git a/tests/writer.docbook b/tests/writer.docbook4 index eee19cdd9..eee19cdd9 100644 --- a/tests/writer.docbook +++ b/tests/writer.docbook4 diff --git a/tests/writer.html b/tests/writer.html4 index 3b63f4e16..3b63f4e16 100644 --- a/tests/writer.html +++ b/tests/writer.html4 diff --git a/tests/writer.html5 b/tests/writer.html5 new file mode 100644 index 000000000..8e0dff764 --- /dev/null +++ b/tests/writer.html5 @@ -0,0 +1,548 @@ +<!DOCTYPE html> +<html> +<head> + <meta charset="utf-8"> + <meta name="generator" content="pandoc"> + <meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes"> + <meta name="author" content="John MacFarlane"> + <meta name="author" content="Anonymous"> + <meta name="dcterms.date" content="2006-07-17"> + <title>Pandoc Test Suite</title> + <style type="text/css">code{white-space: pre;}</style> + <!--[if lt IE 9]> + <script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script> + <![endif]--> +</head> +<body> +<header> +<h1 class="title">Pandoc Test Suite</h1> +<p class="author">John MacFarlane</p> +<p class="author">Anonymous</p> +<p class="date">July 17, 2006</p> +</header> +<p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p> +<hr /> +<h1 id="headers">Headers</h1> +<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url">embedded link</a></h2> +<h3 id="level-3-with-emphasis">Level 3 with <em>emphasis</em></h3> +<h4 id="level-4">Level 4</h4> +<h5 id="level-5">Level 5</h5> +<h1 id="level-1">Level 1</h1> +<h2 id="level-2-with-emphasis">Level 2 with <em>emphasis</em></h2> +<h3 id="level-3">Level 3</h3> +<p>with no blank line</p> +<h2 id="level-2">Level 2</h2> +<p>with no blank line</p> +<hr /> +<h1 id="paragraphs">Paragraphs</h1> +<p>Here’s a regular paragraph.</p> +<p>In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.</p> +<p>Here’s one with a bullet. * criminey.</p> +<p>There should be a hard line break<br /> +here.</p> +<hr /> +<h1 id="block-quotes">Block Quotes</h1> +<p>E-mail style:</p> +<blockquote> +<p>This is a block quote. It is pretty short.</p> +</blockquote> +<blockquote> +<p>Code in a block quote:</p> +<pre><code>sub status { + print "working"; +}</code></pre> +<p>A list:</p> +<ol type="1"> +<li>item one</li> +<li>item two</li> +</ol> +<p>Nested block quotes:</p> +<blockquote> +<p>nested</p> +</blockquote> +<blockquote> +<p>nested</p> +</blockquote> +</blockquote> +<p>This should not be a block quote: 2 > 1.</p> +<p>And a following paragraph.</p> +<hr /> +<h1 id="code-blocks">Code Blocks</h1> +<p>Code:</p> +<pre><code>---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab</code></pre> +<p>And:</p> +<pre><code> this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{</code></pre> +<hr /> +<h1 id="lists">Lists</h1> +<h2 id="unordered">Unordered</h2> +<p>Asterisks tight:</p> +<ul> +<li>asterisk 1</li> +<li>asterisk 2</li> +<li>asterisk 3</li> +</ul> +<p>Asterisks loose:</p> +<ul> +<li><p>asterisk 1</p></li> +<li><p>asterisk 2</p></li> +<li><p>asterisk 3</p></li> +</ul> +<p>Pluses tight:</p> +<ul> +<li>Plus 1</li> +<li>Plus 2</li> +<li>Plus 3</li> +</ul> +<p>Pluses loose:</p> +<ul> +<li><p>Plus 1</p></li> +<li><p>Plus 2</p></li> +<li><p>Plus 3</p></li> +</ul> +<p>Minuses tight:</p> +<ul> +<li>Minus 1</li> +<li>Minus 2</li> +<li>Minus 3</li> +</ul> +<p>Minuses loose:</p> +<ul> +<li><p>Minus 1</p></li> +<li><p>Minus 2</p></li> +<li><p>Minus 3</p></li> +</ul> +<h2 id="ordered">Ordered</h2> +<p>Tight:</p> +<ol type="1"> +<li>First</li> +<li>Second</li> +<li>Third</li> +</ol> +<p>and:</p> +<ol type="1"> +<li>One</li> +<li>Two</li> +<li>Three</li> +</ol> +<p>Loose using tabs:</p> +<ol type="1"> +<li><p>First</p></li> +<li><p>Second</p></li> +<li><p>Third</p></li> +</ol> +<p>and using spaces:</p> +<ol type="1"> +<li><p>One</p></li> +<li><p>Two</p></li> +<li><p>Three</p></li> +</ol> +<p>Multiple paragraphs:</p> +<ol type="1"> +<li><p>Item 1, graf one.</p> +<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.</p></li> +<li><p>Item 2.</p></li> +<li><p>Item 3.</p></li> +</ol> +<h2 id="nested">Nested</h2> +<ul> +<li>Tab +<ul> +<li>Tab +<ul> +<li>Tab</li> +</ul></li> +</ul></li> +</ul> +<p>Here’s another:</p> +<ol type="1"> +<li>First</li> +<li>Second: +<ul> +<li>Fee</li> +<li>Fie</li> +<li>Foe</li> +</ul></li> +<li>Third</li> +</ol> +<p>Same thing but with paragraphs:</p> +<ol type="1"> +<li><p>First</p></li> +<li><p>Second:</p> +<ul> +<li>Fee</li> +<li>Fie</li> +<li>Foe</li> +</ul></li> +<li><p>Third</p></li> +</ol> +<h2 id="tabs-and-spaces">Tabs and spaces</h2> +<ul> +<li><p>this is a list item indented with tabs</p></li> +<li><p>this is a list item indented with spaces</p> +<ul> +<li><p>this is an example list item indented with tabs</p></li> +<li><p>this is an example list item indented with spaces</p></li> +</ul></li> +</ul> +<h2 id="fancy-list-markers">Fancy list markers</h2> +<ol start="2" type="1"> +<li>begins with 2</li> +<li><p>and now 3</p> +<p>with a continuation</p> +<ol start="4" type="i"> +<li>sublist with roman numerals, starting with 4</li> +<li>more items +<ol type="A"> +<li>a subsublist</li> +<li>a subsublist</li> +</ol></li> +</ol></li> +</ol> +<p>Nesting:</p> +<ol type="A"> +<li>Upper Alpha +<ol type="I"> +<li>Upper Roman. +<ol start="6" type="1"> +<li>Decimal start with 6 +<ol start="3" type="a"> +<li>Lower alpha with paren</li> +</ol></li> +</ol></li> +</ol></li> +</ol> +<p>Autonumbering:</p> +<ol> +<li>Autonumber.</li> +<li>More. +<ol> +<li>Nested.</li> +</ol></li> +</ol> +<p>Should not be a list item:</p> +<p>M.A. 2007</p> +<p>B. Williams</p> +<hr /> +<h1 id="definition-lists">Definition Lists</h1> +<p>Tight using spaces:</p> +<dl> +<dt>apple</dt> +<dd>red fruit +</dd> +<dt>orange</dt> +<dd>orange fruit +</dd> +<dt>banana</dt> +<dd>yellow fruit +</dd> +</dl> +<p>Tight using tabs:</p> +<dl> +<dt>apple</dt> +<dd>red fruit +</dd> +<dt>orange</dt> +<dd>orange fruit +</dd> +<dt>banana</dt> +<dd>yellow fruit +</dd> +</dl> +<p>Loose:</p> +<dl> +<dt>apple</dt> +<dd><p>red fruit</p> +</dd> +<dt>orange</dt> +<dd><p>orange fruit</p> +</dd> +<dt>banana</dt> +<dd><p>yellow fruit</p> +</dd> +</dl> +<p>Multiple blocks with italics:</p> +<dl> +<dt><em>apple</em></dt> +<dd><p>red fruit</p> +<p>contains seeds, crisp, pleasant to taste</p> +</dd> +<dt><em>orange</em></dt> +<dd><p>orange fruit</p> +<pre><code>{ orange code block }</code></pre> +<blockquote> +<p>orange block quote</p> +</blockquote> +</dd> +</dl> +<p>Multiple definitions, tight:</p> +<dl> +<dt>apple</dt> +<dd>red fruit +</dd> +<dd>computer +</dd> +<dt>orange</dt> +<dd>orange fruit +</dd> +<dd>bank +</dd> +</dl> +<p>Multiple definitions, loose:</p> +<dl> +<dt>apple</dt> +<dd><p>red fruit</p> +</dd> +<dd><p>computer</p> +</dd> +<dt>orange</dt> +<dd><p>orange fruit</p> +</dd> +<dd><p>bank</p> +</dd> +</dl> +<p>Blank line after term, indented marker, alternate markers:</p> +<dl> +<dt>apple</dt> +<dd><p>red fruit</p> +</dd> +<dd><p>computer</p> +</dd> +<dt>orange</dt> +<dd><p>orange fruit</p> +<ol type="1"> +<li>sublist</li> +<li>sublist</li> +</ol> +</dd> +</dl> +<h1 id="html-blocks">HTML Blocks</h1> +<p>Simple block on one line:</p> +<div> +foo +</div> +<p>And nested without indentation:</p> +<div> +<div> +<div> +<p>foo</p> +</div> +</div> +<div> +bar +</div> +</div> +<p>Interpreted markdown in a table:</p> +<table> +<tr> +<td> +This is <em>emphasized</em> +</td> +<td> +And this is <strong>strong</strong> +</td> +</tr> +</table> +<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> +<p>Here’s a simple block:</p> +<div> +<p>foo</p> +</div> +<p>This should be a code block, though:</p> +<pre><code><div> + foo +</div></code></pre> +<p>As should this:</p> +<pre><code><div>foo</div></code></pre> +<p>Now, nested:</p> +<div> +<div> +<div> +foo +</div> +</div> +</div> +<p>This should just be an HTML comment:</p> +<!-- Comment --> +<p>Multiline:</p> +<!-- +Blah +Blah +--> +<!-- + This is another comment. +--> +<p>Code block:</p> +<pre><code><!-- Comment --></code></pre> +<p>Just plain comment, with trailing spaces on the line:</p> +<!-- foo --> +<p>Code:</p> +<pre><code><hr /></code></pre> +<p>Hr’s:</p> +<hr> +<hr /> +<hr /> +<hr> +<hr /> +<hr /> +<hr class="foo" id="bar" /> +<hr class="foo" id="bar" /> +<hr class="foo" id="bar"> +<hr /> +<h1 id="inline-markup">Inline Markup</h1> +<p>This is <em>emphasized</em>, and so <em>is this</em>.</p> +<p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p> +<p>An <em><a href="/url">emphasized link</a></em>.</p> +<p><strong><em>This is strong and em.</em></strong></p> +<p>So is <strong><em>this</em></strong> word.</p> +<p><strong><em>This is strong and em.</em></strong></p> +<p>So is <strong><em>this</em></strong> word.</p> +<p>This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code><html></code>.</p> +<p><del>This is <em>strikeout</em>.</del></p> +<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup> a<sup>hello there</sup>.</p> +<p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.</p> +<p>These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</p> +<hr /> +<h1 id="smart-quotes-ellipses-dashes">Smart quotes, ellipses, dashes</h1> +<p>“Hello,” said the spider. “‘Shelob’ is my name.”</p> +<p>‘A’, ‘B’, and ‘C’ are letters.</p> +<p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p> +<p>‘He said, “I want to go.”’ Were you alive in the 70’s?</p> +<p>Here is some quoted ‘<code>code</code>’ and a “<a href="http://example.com/?foo=1&bar=2">quoted link</a>”.</p> +<p>Some dashes: one—two — three—four — five.</p> +<p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p> +<p>Ellipses…and…and….</p> +<hr /> +<h1 id="latex">LaTeX</h1> +<ul> +<li></li> +<li><span class="math inline">2 + 2 = 4</span></li> +<li><span class="math inline"><em>x</em> ∈ <em>y</em></span></li> +<li><span class="math inline"><em>α</em> ∧ <em>ω</em></span></li> +<li><span class="math inline">223</span></li> +<li><span class="math inline"><em>p</em></span>-Tree</li> +<li>Here’s some display math: <br /><span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></li> +<li>Here’s one that has a line break in it: <span class="math inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li> +</ul> +<p>These shouldn’t be math:</p> +<ul> +<li>To get the famous equation, write <code>$e = mc^2$</code>.</li> +<li>$22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is emphasized.)</li> +<li>Shoes ($20) and socks ($5).</li> +<li>Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.</li> +</ul> +<p>Here’s a LaTeX table:</p> + +<hr /> +<h1 id="special-characters">Special Characters</h1> +<p>Here is some unicode:</p> +<ul> +<li>I hat: Î</li> +<li>o umlaut: ö</li> +<li>section: §</li> +<li>set membership: ∈</li> +<li>copyright: ©</li> +</ul> +<p>AT&T has an ampersand in their name.</p> +<p>AT&T is another way to write it.</p> +<p>This & that.</p> +<p>4 < 5.</p> +<p>6 > 5.</p> +<p>Backslash: \</p> +<p>Backtick: `</p> +<p>Asterisk: *</p> +<p>Underscore: _</p> +<p>Left brace: {</p> +<p>Right brace: }</p> +<p>Left bracket: [</p> +<p>Right bracket: ]</p> +<p>Left paren: (</p> +<p>Right paren: )</p> +<p>Greater-than: ></p> +<p>Hash: #</p> +<p>Period: .</p> +<p>Bang: !</p> +<p>Plus: +</p> +<p>Minus: -</p> +<hr /> +<h1 id="links">Links</h1> +<h2 id="explicit">Explicit</h2> +<p>Just a <a href="/url/">URL</a>.</p> +<p><a href="/url/" title="title">URL and title</a>.</p> +<p><a href="/url/" title="title preceded by two spaces">URL and title</a>.</p> +<p><a href="/url/" title="title preceded by a tab">URL and title</a>.</p> +<p><a href="/url/" title="title with "quotes" in it">URL and title</a></p> +<p><a href="/url/" title="title with single quotes">URL and title</a></p> +<p><a href="/url/with_underscore">with_underscore</a></p> +<p><a href="mailto:nobody@nowhere.net">Email link</a></p> +<p><a href="">Empty</a>.</p> +<h2 id="reference">Reference</h2> +<p>Foo <a href="/url/">bar</a>.</p> +<p>Foo <a href="/url/">bar</a>.</p> +<p>Foo <a href="/url/">bar</a>.</p> +<p>With <a href="/url/">embedded [brackets]</a>.</p> +<p><a href="/url/">b</a> by itself should be a link.</p> +<p>Indented <a href="/url">once</a>.</p> +<p>Indented <a href="/url">twice</a>.</p> +<p>Indented <a href="/url">thrice</a>.</p> +<p>This should [not][] be a link.</p> +<pre><code>[not]: /url</code></pre> +<p>Foo <a href="/url/" title="Title with "quotes" inside">bar</a>.</p> +<p>Foo <a href="/url/" title="Title with "quote" inside">biz</a>.</p> +<h2 id="with-ampersands">With ampersands</h2> +<p>Here’s a <a href="http://example.com/?foo=1&bar=2">link with an ampersand in the URL</a>.</p> +<p>Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T">AT&T</a>.</p> +<p>Here’s an <a href="/script?foo=1&bar=2">inline link</a>.</p> +<p>Here’s an <a href="/script?foo=1&bar=2">inline link in pointy braces</a>.</p> +<h2 id="autolinks">Autolinks</h2> +<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2" class="uri">http://example.com/?foo=1&bar=2</a></p> +<ul> +<li>In a list?</li> +<li><a href="http://example.com/" class="uri">http://example.com/</a></li> +<li>It should.</li> +</ul> +<p>An e-mail address: <a href="mailto:nobody@nowhere.net">nobody@nowhere.net</a></p> +<blockquote> +<p>Blockquoted: <a href="http://example.com/" class="uri">http://example.com/</a></p> +</blockquote> +<p>Auto-links should not occur here: <code><http://example.com/></code></p> +<pre><code>or here: <http://example.com/></code></pre> +<hr /> +<h1 id="images">Images</h1> +<p>From “Voyage dans la Lune” by Georges Melies (1902):</p> +<figure> +<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" /><figcaption>lalune</figcaption> +</figure> +<p>Here is a movie <img src="movie.jpg" alt="movie" /> icon.</p> +<hr /> +<h1 id="footnotes">Footnotes</h1> +<p>Here is a footnote reference,<a href="#fn1" class="footnoteRef" id="fnref1"><sup>1</sup></a> and another.<a href="#fn2" class="footnoteRef" id="fnref2"><sup>2</sup></a> This should <em>not</em> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a href="#fn3" class="footnoteRef" id="fnref3"><sup>3</sup></a></p> +<blockquote> +<p>Notes can go in quotes.<a href="#fn4" class="footnoteRef" id="fnref4"><sup>4</sup></a></p> +</blockquote> +<ol type="1"> +<li>And in list items.<a href="#fn5" class="footnoteRef" id="fnref5"><sup>5</sup></a></li> +</ol> +<p>This paragraph should not be part of the note, as it is not indented.</p> +<section class="footnotes"> +<hr /> +<ol> +<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.<a href="#fnref1">↩</a></p></li> +<li id="fn2"><p>Here’s the long note. This one contains multiple blocks.</p> +<p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p> +<pre><code> { <code> }</code></pre> +<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.<a href="#fnref2">↩</a></p></li> +<li id="fn3"><p>This is <em>easier</em> to type. Inline notes may contain <a href="http://google.com">links</a> and <code>]</code> verbatim characters, as well as [bracketed text].<a href="#fnref3">↩</a></p></li> +<li id="fn4"><p>In quote.<a href="#fnref4">↩</a></p></li> +<li id="fn5"><p>In list.<a href="#fnref5">↩</a></p></li> +</ol> +</section> +</body> +</html> diff --git a/tests/writer.markdown b/tests/writer.markdown index 4f91a803b..3fe0f4b3e 100644 --- a/tests/writer.markdown +++ b/tests/writer.markdown @@ -6,7 +6,7 @@ date: 'July 17, 2006' title: Pandoc Test Suite --- -This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. ------------------------------------------------------------------------------ @@ -43,13 +43,13 @@ with no blank line Paragraphs ========== -Here’s a regular paragraph. +Here's a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. -Here’s one with a bullet. \* criminey. +Here's one with a bullet. \* criminey. There should be a hard line break\ here. @@ -190,7 +190,7 @@ Multiple paragraphs: 1. Item 1, graf one. - Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + Item 1. graf two. The quick brown fox jumped over the lazy dog's back. 2. Item 2. @@ -203,7 +203,7 @@ Nested - Tab - Tab -Here’s another: +Here's another: 1. First 2. Second: @@ -409,7 +409,7 @@ And this is **strong** </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> -Here’s a simple block: +Here's a simple block: <div> @@ -466,7 +466,7 @@ Code: <hr /> -Hr’s: +Hr's: <hr> <hr /> @@ -513,22 +513,22 @@ spaces: a\^b c\^d, a\~b c\~d. Smart quotes, ellipses, dashes ============================== -“Hello,” said the spider. “‘Shelob’ is my name.” +"Hello," said the spider. "'Shelob' is my name." -‘A’, ‘B’, and ‘C’ are letters. +'A', 'B', and 'C' are letters. -‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ +'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.' -‘He said, “I want to go.”’ Were you alive in the 70’s? +'He said, "I want to go."' Were you alive in the 70's? -Here is some quoted ‘`code`’ and a “[quoted -link](http://example.com/?foo=1&bar=2)”. +Here is some quoted '`code`' and a "[quoted +link](http://example.com/?foo=1&bar=2)". -Some dashes: one—two — three—four — five. +Some dashes: one---two --- three---four --- five. -Dashes between numbers: 5–7, 255–66, 1987–1999. +Dashes between numbers: 5--7, 255--66, 1987--1999. -Ellipses…and…and…. +Ellipses...and...and.... ------------------------------------------------------------------------------ @@ -541,19 +541,19 @@ LaTeX - $\alpha \wedge \omega$ - $223$ - $p$-Tree -- Here’s some display math: +- Here's some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ -- Here’s one that has a line break in it: $\alpha + \omega \times x^2$. +- Here's one that has a line break in it: $\alpha + \omega \times x^2$. -These shouldn’t be math: +These shouldn't be math: - To get the famous equation, write `$e = mc^2$`. -- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is +- \$22,000 is a *lot* of money. So is \$34,000. (It worked if "lot" is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. -Here’s a LaTeX table: +Here's a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline @@ -672,14 +672,14 @@ Foo [biz](/url/ "Title with "quote" inside"). With ampersands --------------- -Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). +Here's a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). -Here’s a link with an amersand in the link text: +Here's a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). -Here’s an [inline link](/script?foo=1&bar=2). +Here's an [inline link](/script?foo=1&bar=2). -Here’s an [inline link in pointy braces](/script?foo=1&bar=2). +Here's an [inline link in pointy braces](/script?foo=1&bar=2). Autolinks --------- @@ -703,7 +703,7 @@ Auto-links should not occur here: `<http://example.com/>` Images ====== -From “Voyage dans la Lune” by Georges Melies (1902): +From "Voyage dans la Lune" by Georges Melies (1902):  @@ -727,7 +727,7 @@ This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. -[^2]: Here’s the long note. This one contains multiple blocks. +[^2]: Here's the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). diff --git a/tests/writer.opml b/tests/writer.opml index c94a88f77..261f83426 100644 --- a/tests/writer.opml +++ b/tests/writer.opml @@ -24,7 +24,7 @@ <outline text="Level 2" _note="with no blank line ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break\ here. ------------------------------------------------------------------------"> +<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break here. ------------------------------------------------------------------------"> </outline> <outline text="Block Quotes" _note="E-mail style: > This is a block quote. It is pretty short. > Code in a block quote: > > sub status { > print "working"; > } > > A list: > > 1. item one > 2. item two > > Nested block quotes: > > > nested > > > nested This should not be a block quote: 2 &gt; 1. And a following paragraph. ------------------------------------------------------------------------"> </outline> @@ -39,18 +39,18 @@ </outline> <outline text="Tabs and spaces" _note="- this is a list item indented with tabs - this is a list item indented with spaces - this is an example list item indented with tabs - this is an example list item indented with spaces "> </outline> - <outline text="Fancy list markers" _note="(2) begins with 2 (3) and now 3 with a continuation iv. sublist with roman numerals, starting with 4 v. more items (A) a subsublist (B) a subsublist Nesting: A. Upper Alpha I. Upper Roman. (6) Decimal start with 6 c) Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams ------------------------------------------------------------------------"> + <outline text="Fancy list markers" _note="1. begins with 2 2. and now 3 with a continuation 1. sublist with roman numerals, starting with 4 2. more items 1. a subsublist 2. a subsublist Nesting: 1. Upper Alpha 1. Upper Roman. 1. Decimal start with 6 1. Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Definition Lists" _note="Tight using spaces: apple : red fruit orange : orange fruit banana : yellow fruit Tight using tabs: apple : red fruit orange : orange fruit banana : yellow fruit Loose: apple : red fruit orange : orange fruit banana : yellow fruit Multiple blocks with italics: *apple* : red fruit contains seeds, crisp, pleasant to taste *orange* : orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple : red fruit : computer orange : orange fruit : bank Multiple definitions, loose: apple : red fruit : computer orange : orange fruit : bank Blank line after term, indented marker, alternate markers: apple : red fruit : computer orange : orange fruit 1. sublist 2. sublist "> +<outline text="Definition Lists" _note="Tight using spaces: apple red fruit orange orange fruit banana yellow fruit Tight using tabs: apple red fruit orange orange fruit banana yellow fruit Loose: apple red fruit orange orange fruit banana yellow fruit Multiple blocks with italics: *apple* red fruit contains seeds, crisp, pleasant to taste *orange* orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple red fruit computer orange orange fruit bank Multiple definitions, loose: apple red fruit computer orange orange fruit bank Blank line after term, indented marker, alternate markers: apple red fruit computer orange orange fruit 1. sublist 2. sublist "> </outline> -<outline text="HTML Blocks" _note="Simple block on one line: <div> foo </div> And nested without indentation: <div> <div> <div> foo </div> </div> <div> bar </div> </div> Interpreted markdown in a table: <table> <tr> <td> This is *emphasized* </td> <td> And this is **strong** </td> </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> Here’s a simple block: <div> foo </div> This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: <div> <div> <div> foo </div> </div> </div> This should just be an HTML comment: <!-- Comment --> Multiline: <!-- Blah Blah --> <!-- This is another comment. --> Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: <!-- foo --> Code: <hr /> Hr’s: <hr> <hr /> <hr /> <hr> <hr /> <hr /> <hr class="foo" id="bar" /> <hr class="foo" id="bar" /> <hr class="foo" id="bar"> ------------------------------------------------------------------------"> +<outline text="HTML Blocks" _note="Simple block on one line: foo And nested without indentation: foo bar Interpreted markdown in a table: This is *emphasized* And this is **strong** Here’s a simple block: foo This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: foo This should just be an HTML comment: Multiline: Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: Code: <hr /> Hr’s: ------------------------------------------------------------------------"> </outline> -<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. ~~This is *strikeout*.~~ Superscripts: a^bc^d a^*hello*^ a^hello there^. Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a\^b c\^d, a\~b c\~d. ------------------------------------------------------------------------"> +<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. This is *strikeout*. Superscripts: abcd a*hello* ahello there. Subscripts: H₂O, H₂₃O, Hmany of themO. These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. ------------------------------------------------------------------------"> </outline> <outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.” ‘A’, ‘B’, and ‘C’ are letters. ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ ‘He said, “I want to go.”’ Were you alive in the 70’s? Here is some quoted ‘`code`’ and a “[quoted link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. ------------------------------------------------------------------------"> </outline> -<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} ------------------------------------------------------------------------"> +<outline text="LaTeX" _note="- - 2 + 2 = 4 - *x* ∈ *y* - *α* ∧ *ω* - 223 - *p*-Tree - Here’s some display math: $$\\frac{d}{dx}f(x)=\\lim\_{h\\to 0}\\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: *α* + *ω* × *x*². These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - $22,000 is a *lot* of money. So is $34,000. (It worked if “lot” is emphasized.) - Shoes ($20) and socks ($5). - Escaped `$`: $73 *this should be emphasized* 23$. Here’s a LaTeX table: ------------------------------------------------------------------------"> </outline> <outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 &lt; 5. 6 &gt; 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: \[ Right bracket: \] Left paren: ( Right paren: ) Greater-than: &gt; Hash: \# Period: . Bang: ! Plus: + Minus: - ------------------------------------------------------------------------"> </outline> @@ -66,7 +66,7 @@ </outline> <outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):  Here is a movie  icon. ------------------------------------------------------------------------"> </outline> -<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be a footnote reference, because it contains a space.\[\^my note\] Here is an inline note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [^2]: Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as \[bracketed text\]. [^4]: In quote. [^5]: In list."> +<outline text="Footnotes" _note="Here is a footnote reference,[1] and another.[2] This should *not* be a footnote reference, because it contains a space.\[^my note\] Here is an inline note.[3] > Notes can go in quotes.[4] 1. And in list items.[5] This paragraph should not be part of the note, as it is not indented. [1] Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [2] Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [3] This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as \[bracketed text\]. [4] In quote. [5] In list."> </outline> </body> </opml> |