From 1673bda95e83aa124241ffdf14d25282d4cad055 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 27 Nov 2016 11:52:42 +0100 Subject: Update tests to work with runPure. --- tests/Tests/Readers/Odt.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index 56711c76b..dff62c54b 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -41,7 +41,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 -- cgit v1.2.3 From 18e85f8dfbf9323945969cdf831c9a16f90299a0 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 27 Nov 2016 16:38:46 +0100 Subject: Changed readNative to use PandocMonad. --- src/Text/Pandoc.hs | 4 ++-- src/Text/Pandoc/Readers/Native.hs | 9 ++++++--- tests/Tests/Old.hs | 4 +++- tests/Tests/Readers/Docx.hs | 4 +++- tests/Tests/Readers/Odt.hs | 4 +++- tests/Tests/Writers/Docx.hs | 8 +++++--- 6 files changed, 22 insertions(+), 11 deletions(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 70d1300b3..34b6b8d0c 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -183,7 +183,7 @@ import Text.Pandoc.Options import Text.Pandoc.Shared (safeRead, warn, mapLeft, pandocVersion) import Text.Pandoc.MediaBag (MediaBag) import Text.Pandoc.Error -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, runIOorExplode) import Data.Aeson import qualified Data.ByteString.Lazy as BL import Data.List (intercalate) @@ -243,7 +243,7 @@ mkBSReaderWithWarnings r = ByteStringReader $ \o s -> -- | Association list of formats and readers. readers :: [(String, Reader IO)] -readers = [ ("native" , StringReader $ \_ s -> return $ readNative s) +readers = [ ("native" , StringReader $ \_ s -> runIOorExplode (readNative s)) ,("json" , mkStringReader readJSON ) ,("markdown" , mkStringReaderWithWarnings readMarkdownWithWarnings) ,("markdown_strict" , mkStringReaderWithWarnings readMarkdownWithWarnings) diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 4ec164e19..917a4a144 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Shared (safeRead) import Text.Pandoc.Error +import Text.Pandoc.Class -- | Read native formatted text and return a Pandoc document. -- The input may be a full pandoc document, a block list, a block, @@ -45,9 +46,11 @@ import Text.Pandoc.Error -- -- > Pandoc nullMeta [Plain [Str "hi"]] -- -readNative :: String -- ^ String to parse (assuming @'\n'@ line endings) - -> Either PandocError Pandoc -readNative s = maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) +readNative :: PandocMonad m + => String -- ^ String to parse (assuming @'\n'@ line endings) + -> m (Either PandocError Pandoc) +readNative s = + return $ maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) readBlocks :: String -> Either PandocError [Block] readBlocks s = maybe ((:[]) <$> readBlock s) Right (safeRead s) diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index bb0e2aac2..b76043887 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -196,7 +196,9 @@ lhsReaderTest :: String -> Test lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm - where normalizer = purely $ writeNative def . normalize . handleError . readNative + where normalizer = purely $ \nat -> do + d <- handleError <$> readNative nat + writeNative def $ normalize d norm = if format == "markdown+lhs" then "lhs-test-markdown.native" else "lhs-test.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 3e630dd49..59147b664 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -14,6 +14,7 @@ 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) -- We define a wrapper around pandoc that doesn't normalize in the -- tests. Since we do our own normalization, we want to make sure @@ -43,7 +44,8 @@ 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)) + df' <- runIOorExplode $ readNative nf + return $ (noNorm p, noNorm $ handleError df') testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index dff62c54b..0ff527130 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -5,6 +5,7 @@ import Text.Pandoc.Options import Text.Pandoc.Readers.Native import Text.Pandoc.Readers.Markdown import Text.Pandoc.Definition +import Text.Pandoc.Class (runIOorExplode) import Tests.Helpers import Test.Framework import qualified Data.ByteString.Lazy as B @@ -62,7 +63,8 @@ compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do nativeFile <- Prelude.readFile nativePath odtFile <- B.readFile odtPath - let native = getNoNormVia id "native" $ readNative nativeFile + native <- getNoNormVia id "native" <$> + runIOorExplode (readNative nativeFile) let odt = getNoNormVia fst "odt" $ readOdt opts odtFile return (odt,native) diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index a76583796..cdaa2c097 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -21,10 +21,12 @@ compareOutput opts nativeFileIn nativeFileOut = do nf <- Prelude.readFile nativeFileIn nf' <- Prelude.readFile nativeFileOut let wopts = fst opts - df <- runIOorExplode $ writeDocx wopts{writerUserDataDir = Just (".." "data")} - (handleError $ readNative nf) + df <- runIOorExplode $ do + d <- handleError <$> readNative nf + writeDocx wopts{writerUserDataDir = Just (".." "data")} d + df' <- handleError <$> runIOorExplode (readNative nf') let (p, _) = handleError $ readDocx (snd opts) df - return (p, handleError $ readNative nf') + return (p, df') testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do -- cgit v1.2.3 From 5ede57122ce61d1504e81c6429ff26c38490aee6 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Thu, 1 Dec 2016 12:47:05 -0500 Subject: Update all tests to use new readers and error structure. --- tests/Tests/Old.hs | 3 +-- tests/Tests/Readers/Docx.hs | 10 +++++----- tests/Tests/Readers/EPUB.hs | 6 ++++-- tests/Tests/Readers/HTML.hs | 2 +- tests/Tests/Readers/LaTeX.hs | 2 +- tests/Tests/Readers/Markdown.hs | 12 ++++++------ tests/Tests/Readers/Odt.hs | 11 +++++------ tests/Tests/Readers/Org.hs | 4 ++-- tests/Tests/Readers/RST.hs | 2 +- tests/Tests/Readers/Txt2Tags.hs | 4 +++- tests/Tests/Writers/Docx.hs | 7 +++---- 11 files changed, 32 insertions(+), 31 deletions(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index b76043887..a8ac717e4 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -19,7 +19,6 @@ import Prelude hiding ( readFile ) import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 (toStringLazy) import Text.Printf -import Text.Pandoc.Error import Tests.Helpers (purely) readFileUTF8 :: FilePath -> IO String @@ -197,7 +196,7 @@ lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm where normalizer = purely $ \nat -> do - d <- handleError <$> readNative nat + d <- readNative nat writeNative def $ normalize d norm = if format == "markdown+lhs" then "lhs-test-markdown.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 59147b664..22fdf575a 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -13,8 +13,8 @@ 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 @@ -43,9 +43,9 @@ compareOutput :: ReaderOptions compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile - let (p, _) = handleError $ readDocx opts df + p <- runIOorExplode $ readDocx opts df df' <- runIOorExplode $ readNative nf - return $ (noNorm p, noNorm $ handleError df') + return $ (noNorm p, noNorm df') testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do @@ -62,7 +62,7 @@ testCompare = testCompareWithOpts def testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test testForWarningsWithOptsIO opts name docxFile expected = do df <- B.readFile docxFile - let (_, _, warns) = handleError $ readDocxWithWarnings opts df + warns <- runIOorExplode (readDocx opts df >> P.getWarnings) return $ test id name (unlines warns, unlines expected) testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> Test @@ -95,7 +95,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 def 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..45e88d90e 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -9,7 +9,7 @@ import Text.Pandoc.Builder import Text.Pandoc latex :: String -> Pandoc -latex = handleError . readLaTeX def +latex = purely $ readLaTeX def infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 439307dc9..b43a0ec49 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -10,17 +10,17 @@ import qualified Data.Set as Set import Text.Pandoc markdown :: String -> Pandoc -markdown = handleError . readMarkdown def +markdown = purely $ readMarkdown def markdownSmart :: String -> Pandoc -markdownSmart = handleError . readMarkdown def { readerSmart = True } +markdownSmart = purely $ readMarkdown def { readerSmart = True } markdownCDL :: String -> Pandoc -markdownCDL = handleError . readMarkdown def { readerExtensions = Set.insert +markdownCDL = purely $ readMarkdown def { readerExtensions = Set.insert Ext_compact_definition_lists $ readerExtensions def } markdownGH :: String -> Pandoc -markdownGH = handleError . readMarkdown def { readerExtensions = githubMarkdownExtensions } +markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c @@ -29,7 +29,7 @@ infix 4 =: testBareLink :: (String, Inlines) -> Test testBareLink (inp, ils) = - test (handleError . readMarkdown def{ readerExtensions = + test (purely $ readMarkdown def{ readerExtensions = Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] }) inp (inp, doc $ para ils) @@ -303,7 +303,7 @@ tests = [ testGroup "inline code" =?> para (note (para "See [^1]")) ] , testGroup "lhs" - [ test (handleError . readMarkdown def{ readerExtensions = Set.insert + [ test (purely $ readMarkdown def{ readerExtensions = Set.insert Ext_literate_haskell $ readerExtensions def }) "inverse bird tracks and html" $ "> a\n\n< b\n\n
\n" diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index 0ff527130..db9184107 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -5,7 +5,7 @@ import Text.Pandoc.Options import Text.Pandoc.Readers.Native import Text.Pandoc.Readers.Markdown import Text.Pandoc.Definition -import Text.Pandoc.Class (runIOorExplode) +import Text.Pandoc.Class (runIOorExplode, runIO, withMediaBag) import Tests.Helpers import Test.Framework import qualified Data.ByteString.Lazy as B @@ -63,17 +63,16 @@ compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do nativeFile <- Prelude.readFile nativePath odtFile <- B.readFile odtPath - native <- getNoNormVia id "native" <$> - runIOorExplode (readNative nativeFile) - let odt = getNoNormVia fst "odt" $ readOdt opts odtFile + native <- getNoNormVia id "native" <$> runIO (readNative 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 opts markdownFile) + odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,markdown) diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index 72b7e2601..b1db75b83 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -9,10 +9,10 @@ import Text.Pandoc import Data.List (intersperse) org :: String -> Pandoc -org = handleError . readOrg def +org = purely $ readOrg def orgSmart :: String -> Pandoc -orgSmart = handleError . readOrg def { readerSmart = True } +orgSmart = purely $ readOrg def { readerSmart = True } infix 4 =: (=:) :: ToString c 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..33502ba78 100644 --- a/tests/Tests/Readers/Txt2Tags.hs +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -10,8 +10,10 @@ import Text.Pandoc import Data.List (intersperse) import Text.Pandoc.Readers.Txt2Tags + t2t :: String -> Pandoc -t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def +-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def +t2t = purely $ readTxt2Tags def infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index cdaa2c097..548e9ddcf 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -7,7 +7,6 @@ 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) @@ -22,10 +21,10 @@ compareOutput opts nativeFileIn nativeFileOut = do nf' <- Prelude.readFile nativeFileOut let wopts = fst opts df <- runIOorExplode $ do - d <- handleError <$> readNative nf + d <- readNative nf writeDocx wopts{writerUserDataDir = Just (".." "data")} d - df' <- handleError <$> runIOorExplode (readNative nf') - let (p, _) = handleError $ readDocx (snd opts) df + df' <- runIOorExplode (readNative nf') + p <- runIOorExplode $ readDocx (snd opts) df return (p, df') testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test -- cgit v1.2.3 From 9d69c51527bd9763a36e52b1995ddc9f79896f58 Mon Sep 17 00:00:00 2001 From: Jesse Rosenthal Date: Fri, 2 Dec 2016 07:34:53 -0500 Subject: ODT test: remove unnecessary imports. --- tests/Tests/Readers/Odt.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index db9184107..c3a44a729 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -5,7 +5,7 @@ import Text.Pandoc.Options import Text.Pandoc.Readers.Native import Text.Pandoc.Readers.Markdown import Text.Pandoc.Definition -import Text.Pandoc.Class (runIOorExplode, runIO, withMediaBag) +import Text.Pandoc.Class (runIO) import Tests.Helpers import Test.Framework import qualified Data.ByteString.Lazy as B -- cgit v1.2.3 From 2e7b0c7edaac9fbba52ac3cbc6380dbfb74805cf Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 10 Dec 2016 16:52:35 +0100 Subject: Added ReaderOptions parameter to readNative. This makes it similar to the other readers -- even though ReaderOptions is essentially ignored, the uniformity is nice. --- src/Text/Pandoc.hs | 2 +- src/Text/Pandoc/Readers/Native.hs | 6 ++++-- tests/Tests/Old.hs | 2 +- tests/Tests/Readers/Docx.hs | 2 +- tests/Tests/Readers/Odt.hs | 2 +- tests/Tests/Writers/Docx.hs | 4 ++-- 6 files changed, 10 insertions(+), 8 deletions(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 013a9d9ac..e5fc665a7 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -238,7 +238,7 @@ data Reader m = StringReader (ReaderOptions -> String -> m Pandoc) -- | Association list of formats and readers. readers :: PandocMonad m => [(String, Reader m)] -readers = [ ("native" , StringReader $ \_ s -> readNative s) +readers = [ ("native" , StringReader readNative) ,("json" , StringReader $ \o s -> case readJSON o s of Right doc -> return doc diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 3e934e43f..1953c0c83 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -32,6 +32,7 @@ module Text.Pandoc.Readers.Native ( readNative ) where import Text.Pandoc.Definition import Text.Pandoc.Shared (safeRead) +import Text.Pandoc.Options (ReaderOptions) import Control.Monad.Except (throwError) import Text.Pandoc.Error @@ -48,9 +49,10 @@ import Text.Pandoc.Class -- > Pandoc nullMeta [Plain [Str "hi"]] -- readNative :: PandocMonad m - => String -- ^ String to parse (assuming @'\n'@ line endings) + => ReaderOptions + -> String -- ^ String to parse (assuming @'\n'@ line endings) -> m Pandoc -readNative s = +readNative _ s = case maybe (Pandoc nullMeta <$> readBlocks s) Right (safeRead s) of Right doc -> return doc Left _ -> throwError $ PandocParseError "couldn't read native" diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 04612d49d..cc35c8aa0 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -196,7 +196,7 @@ lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm where normalizer = purely $ \nat -> do - d <- readNative nat + d <- readNative def nat writeNative def $ normalize d norm = if format == "markdown+lhs" then "lhs-test-markdown.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 22fdf575a..ef060b8ae 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -44,7 +44,7 @@ compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile p <- runIOorExplode $ readDocx opts df - df' <- runIOorExplode $ readNative nf + df' <- runIOorExplode $ readNative def nf return $ (noNorm p, noNorm df') testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index c3a44a729..b0e916336 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -63,7 +63,7 @@ compareOdtToNative :: TestCreator compareOdtToNative opts odtPath nativePath = do nativeFile <- Prelude.readFile nativePath odtFile <- B.readFile odtPath - native <- getNoNormVia id "native" <$> runIO (readNative nativeFile) + native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,native) diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index 44095925f..fd320d224 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -21,9 +21,9 @@ compareOutput opts nativeFileIn nativeFileOut = do nf' <- Prelude.readFile nativeFileOut let wopts = fst opts df <- runIOorExplode $ do - d <- readNative nf + d <- readNative def nf writeDocx wopts{writerUserDataDir = Just (".." "data")} d - df' <- runIOorExplode (readNative nf') + df' <- runIOorExplode (readNative def nf') p <- runIOorExplode $ readDocx (snd opts) df return (p, df') -- cgit v1.2.3 From 4f6e6247f9a672770a6d7a55a3aa2709a860ff38 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 15 Jan 2017 20:42:00 +0100 Subject: Made `smart` extension default for pandoc markdown. Updated tests. --- MANUAL.txt | 41 +++++++++++++++---------------- pandoc.hs | 8 ------ src/Text/Pandoc/Extensions.hs | 1 + tests/Tests/Old.hs | 4 +-- tests/Tests/Readers/Docx.hs | 12 +++++---- tests/Tests/Readers/LaTeX.hs | 3 ++- tests/Tests/Readers/Markdown.hs | 12 +++++---- tests/Tests/Readers/Odt.hs | 16 ++++++------ tests/Tests/Readers/Org.hs | 6 ++--- tests/Tests/Writers/Markdown.hs | 15 +++++++----- tests/fb2/basic.fb2 | 3 ++- tests/fb2/titles.fb2 | 3 ++- tests/markdown-citations.native | 16 ++++++------ tests/tables-rstsubset.native | 8 +++--- tests/tables.asciidoc | 8 +++--- tests/tables.docbook | 8 +++--- tests/tables.docbook5 | 8 +++--- tests/tables.dokuwiki | 8 +++--- tests/tables.fb2 | 3 ++- tests/tables.haddock | 8 +++--- tests/tables.html | 8 +++--- tests/tables.icml | 8 +++--- tests/tables.man | 8 +++--- tests/tables.mediawiki | 8 +++--- tests/tables.native | 8 +++--- tests/tables.opendocument | 8 +++--- tests/tables.plain | 8 +++--- tests/tables.rst | 8 +++--- tests/tables.rtf | 8 +++--- tests/tables.tei | 6 ++--- tests/tables.zimwiki | 8 +++--- tests/writer.markdown | 54 ++++++++++++++++++++--------------------- tests/writer.opml | 14 +++++------ 33 files changed, 174 insertions(+), 171 deletions(-) (limited to 'tests/Tests/Readers/Odt.hs') diff --git a/MANUAL.txt b/MANUAL.txt index ec3499513..2b55b8239 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -706,12 +706,10 @@ Options affecting specific writers than parsing ligatures for quotation marks and dashes. In writing LaTeX or ConTeXt, print unicode quotation mark and dash characters literally, rather than converting them to - the standard ASCII TeX ligatures. Note: normally the `smart` - extension is selected automatically for LaTeX and ConTeXt output, - but it must be specified explicitly if `--no-tex-ligatures` is - selected. If you use literal curly quotes, dashes, and - ellipses in your source, then you may want to use - `--no-tex-ligatures` without `+smart`. + the standard ASCII TeX ligatures. Note: If you use literal + curly quotes, dashes, and ellipses in your source, then you + may want to use disable the `smart` extension in your + source format. `--listings` @@ -3180,6 +3178,22 @@ they cannot contain multiple paragraphs). The syntax is as follows: Inline and regular footnotes may be mixed freely. +Typography +---------- + +#### Extension: `smart` #### + +Interpret straight quotes as curly quotes, `---` as em-dashes, +`--` as en-dashes, and `...` as ellipses. Nonbreaking spaces are +inserted after certain abbreviations, such as "Mr." + +Note: If you are *writing* Markdown, then the `smart` extension +has the reverse effect: what would have been curly quotes comes +out straight. + +If your LaTeX template or any included header file call +for the [`csquotes`] package, pandoc will detect this +automatically and use `\enquote{...}` for quoted text. Citations --------- @@ -3381,21 +3395,6 @@ in pandoc, but may be enabled by adding `+EXTENSION` to the format name, where `EXTENSION` is the name of the extension. Thus, for example, `markdown+hard_line_breaks` is Markdown with hard line breaks. -#### Extension: `smart` #### - -Interpret straight quotes as curly quotes, `---` as em-dashes, -`--` as en-dashes, and `...` as ellipses. Nonbreaking spaces are -inserted after certain abbreviations, such as "Mr." - -Notes: - - * This extension option is selected automatically when the - output format is `latex` or `context`, unless - `--no-tex-ligatures` is used. It has no effect for `latex` input. - * If your LaTeX template or any included header file call - for the [`csquotes`] package, pandoc will detect this - automatically and use `\enquote{...}` for quoted text. - #### Extension: `old_dashes` #### Selects the pandoc <= 1.8.2.1 behavior for parsing smart dashes: diff --git a/pandoc.hs b/pandoc.hs index 5d3b85f6e..0baf555de 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -289,14 +289,6 @@ convertWithOpts opts args = do uriFragment = "" } _ -> Nothing - {- TODO - smart is now an extension, but we should prob make - - texligatures one too... - let smartExt = if laTeXInput - then texLigatures - else smart || (texLigatures && - (laTeXOutput || conTeXtOutput)) - -} - let readerOpts = def{ readerStandalone = standalone' , readerParseRaw = parseRaw , readerColumns = columns diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 7278ece61..14422ce39 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -177,6 +177,7 @@ pandocExtensions = extensionsFromList , Ext_implicit_header_references , Ext_line_blocks , Ext_shortcut_reference_links + , Ext_smart ] plainExtensions :: Extensions diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index f9a8a71d5..21e00b033 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -47,13 +47,13 @@ tests = [ testGroup "markdown" [ testGroup "writer" $ writerTests "markdown" ++ lhsWriterTests "markdown" , testGroup "reader" - [ test "basic" ["-r", "markdown+smart", "-w", "native", "-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+smart", "-w", "native", "-s"] + , test "more" ["-r", "markdown", "-w", "native", "-s"] "markdown-reader-more.txt" "markdown-reader-more.native" , lhsReaderTest "markdown+lhs" ] diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index ef060b8ae..1fdb29f2e 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -1,7 +1,6 @@ module Tests.Readers.Docx (tests) where -import Text.Pandoc.Options -import Text.Pandoc.Readers.Native +import Text.Pandoc import Text.Pandoc.Definition import Tests.Helpers import Test.Framework @@ -26,6 +25,9 @@ data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} noNorm :: Pandoc -> NoNormPandoc noNorm = NoNormPandoc +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "docx" } + instance ToString NoNormPandoc where toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of @@ -57,7 +59,7 @@ 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 @@ -70,7 +72,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 @@ -95,7 +97,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do compareMediaBagIO :: FilePath -> IO Bool compareMediaBagIO docxFile = do df <- B.readFile docxFile - mb <- runIOorExplode (readDocx def df >> P.getMediaBag) + mb <- runIOorExplode (readDocx defopts df >> P.getMediaBag) bools <- mapM (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) (mediaDirectory mb) diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 45e88d90e..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 = purely $ 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 ff68b4d3f..65edf7c38 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -9,18 +9,20 @@ import Text.Pandoc.Builder import Text.Pandoc markdown :: String -> Pandoc -markdown = purely $ readMarkdown def +markdown = purely $ readMarkdown def { readerExtensions = + disableExtension Ext_smart pandocExtensions } markdownSmart :: String -> Pandoc markdownSmart = purely $ readMarkdown def { readerExtensions = - enableExtension Ext_smart $ readerExtensions def } + enableExtension Ext_smart pandocExtensions } markdownCDL :: String -> Pandoc markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension - Ext_compact_definition_lists $ readerExtensions def } + Ext_compact_definition_lists pandocExtensions } markdownGH :: String -> Pandoc -markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } +markdownGH = purely $ readMarkdown def { + readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c @@ -304,7 +306,7 @@ tests = [ testGroup "inline code" ] , testGroup "lhs" [ test (purely $ readMarkdown def{ readerExtensions = enableExtension - Ext_literate_haskell $ readerExtensions def }) + Ext_literate_haskell pandocExtensions }) "inverse bird tracks and html" $ "> a\n\n< b\n\n
\n" =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a" diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index b0e916336..63283497b 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -1,18 +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 @@ -71,7 +69,9 @@ compareOdtToMarkdown :: TestCreator compareOdtToMarkdown opts odtPath markdownPath = do markdownFile <- Prelude.readFile markdownPath odtFile <- B.readFile odtPath - markdown <- getNoNormVia id "markdown" <$> runIO (readMarkdown opts markdownFile) + markdown <- getNoNormVia id "markdown" <$> + runIO (readMarkdown def{ readerExtensions = pandocExtensions } + markdownFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,markdown) @@ -81,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 ed29f1377..ef0530b37 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -9,11 +9,11 @@ import Text.Pandoc import Data.List (intersperse) org :: String -> Pandoc -org = purely $ readOrg def - +org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } + orgSmart :: String -> Pandoc orgSmart = purely $ readOrg def { readerExtensions = - enableExtension Ext_smart $ readerExtensions def } + enableExtension Ext_smart $ getDefaultExtensions "org" } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index aa8a732f1..abefe27d5 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -8,8 +8,11 @@ import Text.Pandoc import Tests.Helpers import Text.Pandoc.Arbitrary() +defopts :: WriterOptions +defopts = def{ writerExtensions = pandocExtensions } + markdown :: (ToPandoc a) => a -> String -markdown = purely (writeMarkdown def) . toPandoc +markdown = purely (writeMarkdown defopts) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x @@ -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 (purely (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/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 @@ -pandoc<p />

<p>Top-level title</p>
<p>Section</p>
<p>Subsection</p>

This emphasized strong verbatim markdown. See this link[1].

Ordered list:

 1. one

 2. two

 3. three

Blockquote is for citatons.

Code

block

is

for

code.

Strikeout is Pandoc's extension. Superscript and subscripts too: H2O is a liquid[2]. 210 is 1024.

Math is another Pandoc extension: E = m c^2.

<p>1</p>

http://example.com/

<p>2</p>

Sometimes.

\ No newline at end of file +pandoc<p />

<p>Top-level title</p>
<p>Section</p>
<p>Subsection</p>

This emphasized strong verbatim markdown. See this link[1].

Ordered list:

 1. one

 2. two

 3. three

Blockquote is for citatons.

Code

block

is

for

code.

Strikeout is Pandoc’s extension. Superscript and subscripts too: H2O is a liquid[2]. 210 is 1024.

Math is another Pandoc extension: E = m c^2.

<p>1</p>

http://example.com/

<p>2</p>

Sometimes.

+ 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 @@ -pandoc<p />

<p>Simple title</p>

This example tests if Pandoc doesn't insert forbidden elements in FictionBook titles.

<p>Emphasized Strong Title</p>
<p>Title with</p><empty-line /><p>line break</p>
\ No newline at end of file +pandoc<p />

<p>Simple title</p>

This example tests if Pandoc doesn’t insert forbidden elements in FictionBook titles.

<p>Emphasized Strong Title</p>
<p>Title with</p><empty-line /><p>line break</p>
+ 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/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.docbook index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook +++ b/tests/tables.docbook @@ -222,7 +222,7 @@ - Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. @@ -271,7 +271,7 @@ 5.0 - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. @@ -328,7 +328,7 @@ 5.0 - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. @@ -424,7 +424,7 @@ 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.docbook5 b/tests/tables.docbook5 index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook5 +++ b/tests/tables.docbook5 @@ -222,7 +222,7 @@
- Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. @@ -271,7 +271,7 @@ 5.0 - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. @@ -328,7 +328,7 @@ 5.0 - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. @@ -424,7 +424,7 @@ 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.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 @@ -pandoc<p />

Simple table with caption:

RightLeftCenterDefault
12121212
123123123123
1111

Demonstration of simple table syntax.

Simple table without caption:

RightLeftCenterDefault
12121212
123123123123
1111

Simple table indented two spaces:

RightLeftCenterDefault
12121212
123123123123
1111

Demonstration of simple table syntax.

Multiline table with caption:

Centered HeaderLeft AlignedRight AlignedDefault aligned
Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here's another one. Note the blank line between rows.

Here's the caption. It may span multiple lines.

Multiline table without caption:

Centered HeaderLeft AlignedRight AlignedDefault aligned
Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here's another one. Note the blank line between rows.

Table without column headers:

12121212
123123123123
1111

Multiline table without column headers:

Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here's another one. Note the blank line between rows.

\ No newline at end of file +pandoc<p />

Simple table with caption:

RightLeftCenterDefault
12121212
123123123123
1111

Demonstration of simple table syntax.

Simple table without caption:

RightLeftCenterDefault
12121212
123123123123
1111

Simple table indented two spaces:

RightLeftCenterDefault
12121212
123123123123
1111

Demonstration of simple table syntax.

Multiline table with caption:

Centered HeaderLeft AlignedRight AlignedDefault aligned
Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here’s another one. Note the blank line between rows.

Here’s the caption. It may span multiple lines.

Multiline table without caption:

Centered HeaderLeft AlignedRight AlignedDefault aligned
Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here’s another one. Note the blank line between rows.

Table without column headers:

12121212
123123123123
1111

Multiline table without column headers:

Firstrow12.0Example of a row that spans multiple lines.
Secondrow5.0Here’s another one. Note the blank line between rows.

+ 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.html index 0a9ea413c..5bb7a7de2 100644 --- a/tests/tables.html +++ b/tests/tables.html @@ -95,7 +95,7 @@

Multiline table with caption:

- +@@ -121,7 +121,7 @@ - +
Here's the caption. It may span multiple lines.Here’s the caption. It may span multiple lines.
Second row 5.0Here's another one. Note the blank line between rows.Here’s another one. Note the blank line between rows.
@@ -152,7 +152,7 @@ Second row 5.0 -Here's another one. Note the blank line between rows. +Here’s another one. Note the blank line between rows. @@ -198,7 +198,7 @@ Second row 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.icml b/tests/tables.icml index 678f4b7a9..0280cafed 100644 --- a/tests/tables.icml +++ b/tests/tables.icml @@ -476,14 +476,14 @@ - Here's another one. Note the blank line between rows. + 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.
@@ -578,7 +578,7 @@ - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. @@ -748,7 +748,7 @@ - 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.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: 5.0 - Here's another one. Note the + Here’s another one. Note the blank line between rows. -Here's the caption. It may span multiple +Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -302,7 +302,7 @@ caption: 5.0 - Here's another one. Note the + Here’s another one. Note the blank line between rows. @@ -390,7 +390,7 @@ headers: 5.0 - Here's another one. Note the + Here’s another one. Note the blank line between rows. 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 60b088082..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,7 +352,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} 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 @@

Second

row

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:

@@ -118,7 +118,7 @@

Second

row

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:

@@ -166,6 +166,6 @@

Second

row

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.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/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** -Here’s a simple block: +Here's a simple block:
@@ -466,7 +466,7 @@ Code:
-Hr’s: +Hr's:

@@ -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: `` Images ====== -From “Voyage dans la Lune” by Georges Melies (1902): +From "Voyage dans la Lune" by Georges Melies (1902): ![lalune](lalune.jpg "Voyage dans la Lune") @@ -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 @@ - + @@ -39,18 +39,18 @@ - + - + - + - + - + @@ -66,7 +66,7 @@ - + -- cgit v1.2.3