aboutsummaryrefslogtreecommitdiff
path: root/test
diff options
context:
space:
mode:
Diffstat (limited to 'test')
-rw-r--r--test/Tests/Command.hs9
-rw-r--r--test/Tests/Helpers.hs11
-rw-r--r--test/Tests/Lua.hs6
-rw-r--r--test/Tests/Readers/Docx.hs7
-rw-r--r--test/Tests/Readers/HTML.hs3
-rw-r--r--test/Tests/Readers/LaTeX.hs14
-rw-r--r--test/Tests/Readers/Markdown.hs48
-rw-r--r--test/Tests/Readers/Odt.hs10
-rw-r--r--test/Tests/Readers/Org.hs1066
-rw-r--r--test/Tests/Readers/RST.hs24
-rw-r--r--test/Tests/Readers/Txt2Tags.hs78
-rw-r--r--test/Tests/Writers/AsciiDoc.hs3
-rw-r--r--test/Tests/Writers/ConTeXt.hs5
-rw-r--r--test/Tests/Writers/Docbook.hs3
-rw-r--r--test/Tests/Writers/Docx.hs6
-rw-r--r--test/Tests/Writers/HTML.hs3
-rw-r--r--test/Tests/Writers/LaTeX.hs5
-rw-r--r--test/Tests/Writers/Markdown.hs5
-rw-r--r--test/Tests/Writers/Muse.hs21
-rw-r--r--test/Tests/Writers/Native.hs6
-rw-r--r--test/command/1718.md11
-rw-r--r--test/command/1841.md42
-rw-r--r--test/command/2228.md6
-rw-r--r--test/command/2602.md18
-rw-r--r--test/command/3113.md13
-rw-r--r--test/command/3314.md34
-rw-r--r--test/command/3401.md19
-rw-r--r--test/command/3432.md289
-rw-r--r--test/command/3450.md12
-rw-r--r--test/command/3494.md2
-rw-r--r--test/command/3510-export.latex1
-rw-r--r--test/command/3510-src.hs1
-rw-r--r--test/command/3510-subdoc.org5
-rw-r--r--test/command/3510.md20
-rw-r--r--test/command/3516.md4
-rw-r--r--test/command/3577.md2
-rw-r--r--test/command/3585.md16
-rw-r--r--test/command/3619.md28
-rw-r--r--test/command/3630.md8
-rw-r--r--test/command/3667.md13
-rw-r--r--test/command/3674.md39
-rw-r--r--test/command/3675.md15
-rw-r--r--test/command/3690.md8
-rw-r--r--test/command/3701.md60
-rw-r--r--test/command/3706.md44
-rw-r--r--test/command/3708.md15
-rw-r--r--test/command/3715.md15
-rw-r--r--test/command/3716.md6
-rw-r--r--test/command/3730.md21
-rw-r--r--test/command/3736.md25
-rw-r--r--test/command/512.md1
-rw-r--r--test/command/SVG_logo-without-xml-declaration.svg32
-rw-r--r--test/command/SVG_logo.svg33
-rw-r--r--test/command/corrupt.svg5
-rw-r--r--test/command/inkscape-cube.svg119
-rw-r--r--test/command/latex-fontawesome.md13
-rw-r--r--test/command/lstlisting.md25
-rw-r--r--test/command/parse-raw.md3
-rw-r--r--test/command/svg.md132
-rw-r--r--test/command/tabularx.md110
-rw-r--r--test/fb2/titles.fb22
-rw-r--r--test/fb2/titles.markdown4
-rw-r--r--test/latex-reader.native4
-rw-r--r--test/lhs-test.latex12
-rw-r--r--test/lhs-test.latex+lhs12
-rw-r--r--test/markdown-reader-more.native68
-rw-r--r--test/tables-rstsubset.native12
-rw-r--r--test/tables.muse52
-rw-r--r--test/testsuite.native2
-rw-r--r--test/testsuite.txt11
-rw-r--r--test/writer.asciidoc4
-rw-r--r--test/writer.context53
-rw-r--r--test/writer.docbook46
-rw-r--r--test/writer.docbook56
-rw-r--r--test/writer.dokuwiki4
-rw-r--r--test/writer.fb21014
-rw-r--r--test/writer.haddock4
-rw-r--r--test/writer.html42
-rw-r--r--test/writer.html52
-rw-r--r--test/writer.icml126
-rw-r--r--test/writer.jats6
-rw-r--r--test/writer.latex16
-rw-r--r--test/writer.man4
-rw-r--r--test/writer.markdown4
-rw-r--r--test/writer.mediawiki4
-rw-r--r--test/writer.ms10
-rw-r--r--test/writer.muse44
-rw-r--r--test/writer.native2
-rw-r--r--test/writer.opendocument4
-rw-r--r--test/writer.opml2
-rw-r--r--test/writer.org4
-rw-r--r--test/writer.plain4
-rw-r--r--test/writer.rst10
-rw-r--r--test/writer.rtf8
-rw-r--r--test/writer.tei2
-rw-r--r--test/writer.texinfo4
-rw-r--r--test/writer.textile4
-rw-r--r--test/writer.zimwiki4
-rw-r--r--test/writers-lang-and-dir.context13
-rw-r--r--test/writers-lang-and-dir.latex39
100 files changed, 3193 insertions, 993 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
index 054ceb50d..1f3694f60 100644
--- a/test/Tests/Command.hs
+++ b/test/Tests/Command.hs
@@ -13,6 +13,7 @@ import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Shared (trimr)
+import qualified Data.ByteString as BS
import qualified Text.Pandoc.UTF8 as UTF8
import System.IO.Unsafe (unsafePerformIO) -- TODO temporary
@@ -23,7 +24,7 @@ runTest :: String -- ^ Title of test
-> String -- ^ Expected output
-> TestTree
runTest testname cmd inp norm = testCase testname $ do
- let cmd' = cmd ++ " --quiet --data-dir ../data"
+ let cmd' = cmd ++ " --data-dir ../data"
let findDynlibDir [] = Nothing
findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
findDynlibDir (_:xs) = findDynlibDir xs
@@ -35,9 +36,9 @@ runTest testname cmd inp norm = testCase testname $ do
("LD_LIBRARY_PATH", d)]
let env' = dynlibEnv ++ [("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./")]
let pr = (shell cmd'){ env = Just env' }
- (ec, out', _err) <- readCreateProcessWithExitCode pr inp
+ (ec, out', err') <- readCreateProcessWithExitCode pr inp
-- filter \r so the tests will work on Windows machines
- let out = filter (/= '\r') out'
+ let out = filter (/= '\r') $ err' ++ out'
result <- if ec == ExitSuccess
then do
if out == norm
@@ -83,7 +84,7 @@ runCommandTest pandocpath (num, code) =
extractCommandTest :: FilePath -> FilePath -> TestTree
extractCommandTest pandocpath fp = unsafePerformIO $ do
- contents <- UTF8.readFile ("command" </> fp)
+ contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
Pandoc _ blocks <- runIOorExplode (readMarkdown
def{ readerExtensions = pandocExtensions } contents)
let codeblocks = map extractCode $ filter isCodeBlock $ blocks
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
index 7e8ebb01a..2a6543ea0 100644
--- a/test/Tests/Helpers.hs
+++ b/test/Tests/Helpers.hs
@@ -15,6 +15,7 @@ module Tests.Helpers ( test
import Data.Algorithm.Diff
import qualified Data.Map as M
+import Data.Text (Text, unpack)
import System.Directory
import System.Environment.Executable (getExecutablePath)
import System.Exit
@@ -105,21 +106,25 @@ class ToString a where
toString :: a -> String
instance ToString Pandoc where
- toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ toString d = unpack $
+ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
(Pandoc (Meta m) _)
| M.null m -> Nothing
| otherwise -> Just "" -- need this to get meta output
instance ToString Blocks where
- toString = purely (writeNative def) . toPandoc
+ toString = unpack . purely (writeNative def) . toPandoc
instance ToString Inlines where
- toString = trimr . purely (writeNative def) . toPandoc
+ toString = trimr . unpack . purely (writeNative def) . toPandoc
instance ToString String where
toString = id
+instance ToString Text where
+ toString = unpack
+
class ToPandoc a where
toPandoc :: a -> Pandoc
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 50f9634a2..cd8604ab9 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -3,9 +3,9 @@ module Tests.Lua ( tests ) where
import Control.Monad (when)
import System.FilePath ((</>))
-import Test.Tasty (TestTree)
+import Test.Tasty (TestTree, localOption)
import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
-import Test.Tasty.QuickCheck (ioProperty, testProperty)
+import Test.Tasty.QuickCheck (ioProperty, testProperty, QuickCheckTests(..))
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc)
import Text.Pandoc.Builder ( (<>), bulletList, doc, doubleQuoted, emph
@@ -16,7 +16,7 @@ import Text.Pandoc.Lua
import qualified Scripting.Lua as Lua
tests :: [TestTree]
-tests =
+tests = map (localOption (QuickCheckTests 20))
[ testProperty "inline elements can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Inline))
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 028a4ff2f..e55c3529b 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -2,11 +2,14 @@ module Tests.Readers.Docx (tests) where
import Codec.Archive.Zip
import qualified Data.ByteString.Lazy as B
+import qualified Data.ByteString as BS
+import qualified Data.Text as T
import qualified Data.Map as M
import Test.Tasty
import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
+import Text.Pandoc.UTF8 as UTF8
import qualified Text.Pandoc.Class as P
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
import System.IO.Unsafe -- TODO temporary
@@ -25,7 +28,7 @@ defopts :: ReaderOptions
defopts = def{ readerExtensions = getDefaultExtensions "docx" }
instance ToString NoNormPandoc where
- toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ toString d = T.unpack $ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -40,7 +43,7 @@ compareOutput :: ReaderOptions
-> IO (NoNormPandoc, NoNormPandoc)
compareOutput opts docxFile nativeFile = do
df <- B.readFile docxFile
- nf <- Prelude.readFile nativeFile
+ nf <- UTF8.toText <$> BS.readFile nativeFile
p <- runIOorExplode $ readDocx opts df
df' <- runIOorExplode $ readNative def nf
return $ (noNorm p, noNorm df')
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
index e2262d131..8647540b6 100644
--- a/test/Tests/Readers/HTML.hs
+++ b/test/Tests/Readers/HTML.hs
@@ -6,8 +6,9 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import Data.Text (Text)
-html :: String -> Pandoc
+html :: Text -> Pandoc
html = purely $ readHtml def
tests :: [TestTree]
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
index 75547ed6b..afac9e8cb 100644
--- a/test/Tests/Readers/LaTeX.hs
+++ b/test/Tests/Readers/LaTeX.hs
@@ -6,14 +6,16 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import Data.Text (Text)
+import qualified Data.Text as T
-latex :: String -> Pandoc
+latex :: Text -> Pandoc
latex = purely $ readLaTeX def{
readerExtensions = getDefaultExtensions "latex" }
infix 4 =:
(=:) :: ToString c
- => String -> (String, c) -> TestTree
+ => String -> (Text, c) -> TestTree
(=:) = test latex
simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
@@ -74,7 +76,7 @@ tests = [ testGroup "basic"
"\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?>
simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
, "Multi line table" =:
- unlines [ "\\begin{tabular}{|c|}"
+ T.unlines [ "\\begin{tabular}{|c|}"
, "One\\\\"
, "Two\\\\"
, "Three\\\\"
@@ -91,7 +93,7 @@ tests = [ testGroup "basic"
"\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?>
simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
, "Table with custom column separators" =:
- unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}"
+ T.unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}"
, "One&Two\\\\"
, "\\end{tabular}" ] =?>
simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
@@ -108,10 +110,10 @@ tests = [ testGroup "basic"
, let hex = ['0'..'9']++['a'..'f'] in
testGroup "Character Escapes"
[ "Two-character escapes" =:
- concat ["^^"++[i,j] | i <- hex, j <- hex] =?>
+ mconcat ["^^" <> T.pack [i,j] | i <- hex, j <- hex] =?>
para (str ['\0'..'\255'])
, "One-character escapes" =:
- concat ["^^"++[i] | i <- hex] =?>
+ mconcat ["^^" <> T.pack [i] | i <- hex] =?>
para (str $ ['p'..'y']++['!'..'&'])
]
]
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index e1d0c8e1f..1cd32b87d 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -1,38 +1,40 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.Markdown (tests) where
+import Data.Text (Text, unpack)
+import qualified Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
-markdown :: String -> Pandoc
+markdown :: Text -> Pandoc
markdown = purely $ readMarkdown def { readerExtensions =
disableExtension Ext_smart pandocExtensions }
-markdownSmart :: String -> Pandoc
+markdownSmart :: Text -> Pandoc
markdownSmart = purely $ readMarkdown def { readerExtensions =
enableExtension Ext_smart pandocExtensions }
-markdownCDL :: String -> Pandoc
+markdownCDL :: Text -> Pandoc
markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension
Ext_compact_definition_lists pandocExtensions }
-markdownGH :: String -> Pandoc
+markdownGH :: Text -> Pandoc
markdownGH = purely $ readMarkdown def {
readerExtensions = githubMarkdownExtensions }
infix 4 =:
(=:) :: ToString c
- => String -> (String, c) -> TestTree
+ => String -> (Text, c) -> TestTree
(=:) = test markdown
-testBareLink :: (String, Inlines) -> TestTree
+testBareLink :: (Text, Inlines) -> TestTree
testBareLink (inp, ils) =
test (purely $ readMarkdown def{ readerExtensions =
extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] })
- inp (inp, doc $ para ils)
+ (unpack inp) (inp, doc $ para ils)
autolink :: String -> Inlines
autolink = autolinkWith nullAttr
@@ -40,7 +42,7 @@ autolink = autolinkWith nullAttr
autolinkWith :: Attr -> String -> Inlines
autolinkWith attr s = linkWith attr s "" (str s)
-bareLinkTests :: [(String, Inlines)]
+bareLinkTests :: [(Text, Inlines)]
bareLinkTests =
[ ("http://google.com is a search engine.",
autolink "http://google.com" <> " is a search engine.")
@@ -376,10 +378,10 @@ tests = [ testGroup "inline code"
rawBlock "html" "</button>" <>
divWith nullAttr (para $ text "with this div too.")]
, test markdownGH "issue #1636" $
- unlines [ "* a"
- , "* b"
- , "* c"
- , " * d" ]
+ T.unlines [ "* a"
+ , "* b"
+ , "* c"
+ , " * d" ]
=?>
bulletList [ plain "a"
, plain "b"
@@ -419,9 +421,9 @@ tests = [ testGroup "inline code"
, let citation = cite [Citation "cita" [] [] AuthorInText 0 0] (str "@cita")
in testGroup "footnote/link following citation" -- issue #2083
[ "footnote" =:
- unlines [ "@cita[^note]"
- , ""
- , "[^note]: note" ] =?>
+ T.unlines [ "@cita[^note]"
+ , ""
+ , "[^note]: note" ] =?>
para (
citation <> note (para $ str "note")
)
@@ -431,22 +433,22 @@ tests = [ testGroup "inline code"
citation <> space <> link "http://www.com" "" (str "link")
)
, "reference link" =:
- unlines [ "@cita [link][link]"
- , ""
- , "[link]: http://www.com" ] =?>
+ T.unlines [ "@cita [link][link]"
+ , ""
+ , "[link]: http://www.com" ] =?>
para (
citation <> space <> link "http://www.com" "" (str "link")
)
, "short reference link" =:
- unlines [ "@cita [link]"
- , ""
- , "[link]: http://www.com" ] =?>
+ T.unlines [ "@cita [link]"
+ , ""
+ , "[link]: http://www.com" ] =?>
para (
citation <> space <> link "http://www.com" "" (str "link")
)
, "implicit header link" =:
- unlines [ "# Header"
- , "@cita [Header]" ] =?>
+ T.unlines [ "# Header"
+ , "@cita [Header]" ] =?>
headerWith ("header",[],[]) 1 (str "Header") <> para (
citation <> space <> link "#header" "" (str "Header")
)
diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs
index 6fc062158..eed3a33b0 100644
--- a/test/Tests/Readers/Odt.hs
+++ b/test/Tests/Readers/Odt.hs
@@ -2,7 +2,10 @@ module Tests.Readers.Odt (tests) where
import Control.Monad (liftM)
import qualified Data.ByteString.Lazy as B
+import qualified Data.ByteString as BS
+import qualified Text.Pandoc.UTF8 as UTF8
import qualified Data.Map as M
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -39,7 +42,8 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
deriving ( Show )
instance ToString NoNormPandoc where
- toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
+ toString d = unpack $
+ purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -58,7 +62,7 @@ type TestCreator = ReaderOptions
compareOdtToNative :: TestCreator
compareOdtToNative opts odtPath nativePath = do
- nativeFile <- Prelude.readFile nativePath
+ nativeFile <- UTF8.toText <$> BS.readFile nativePath
odtFile <- B.readFile odtPath
native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile)
odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
@@ -66,7 +70,7 @@ compareOdtToNative opts odtPath nativePath = do
compareOdtToMarkdown :: TestCreator
compareOdtToMarkdown opts odtPath markdownPath = do
- markdownFile <- Prelude.readFile markdownPath
+ markdownFile <- UTF8.toText <$> BS.readFile markdownPath
odtFile <- B.readFile odtPath
markdown <- getNoNormVia id "markdown" <$>
runIO (readMarkdown def{ readerExtensions = pandocExtensions }
diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs
index 7a7960396..45b10da42 100644
--- a/test/Tests/Readers/Org.hs
+++ b/test/Tests/Readers/Org.hs
@@ -2,21 +2,23 @@
module Tests.Readers.Org (tests) where
import Data.List (intersperse)
+import Data.Text (Text)
+import qualified Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Builder
-org :: String -> Pandoc
+org :: Text -> Pandoc
org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
-orgSmart :: String -> Pandoc
+orgSmart :: Text -> Pandoc
orgSmart = purely $ readOrg def { readerExtensions =
enableExtension Ext_smart $ getDefaultExtensions "org" }
infix 4 =:
(=:) :: ToString c
- => String -> (String, c) -> TestTree
+ => String -> (Text, c) -> TestTree
(=:) = test org
spcSep :: [Inlines] -> Inlines
@@ -26,7 +28,11 @@ simpleTable' :: Int
-> [Blocks]
-> [[Blocks]]
-> Blocks
-simpleTable' n = table "" (take n $ repeat (AlignDefault, 0.0))
+simpleTable' n = table "" (replicate n (AlignDefault, 0.0))
+
+-- | Create a span for the given tag.
+tagSpan :: String -> Inlines
+tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) . smallcaps $ str t
tests :: [TestTree]
tests =
@@ -108,17 +114,17 @@ tests =
para (note $ para "Schreib mir eine E-Mail")
, "Markup-chars not occuring on word break are symbols" =:
- unlines [ "this+that+ +so+on"
- , "seven*eight* nine*"
- , "+not+funny+"
- ] =?>
+ T.unlines [ "this+that+ +so+on"
+ , "seven*eight* nine*"
+ , "+not+funny+"
+ ] =?>
para ("this+that+ +so+on" <> softbreak <>
"seven*eight* nine*" <> softbreak <>
strikeout "not+funny")
, "No empty markup" =:
- "// ** __ ++ == ~~ $$" =?>
- para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ])
+ "// ** __ <> == ~~ $$" =?>
+ para (spcSep [ "//", "**", "__", "<>", "==", "~~", "$$" ])
, "Adherence to Org's rules for markup borders" =:
"/t/& a/ / ./r/ (*l*) /e/! /b/." =?>
@@ -139,11 +145,11 @@ tests =
para "/nada,/"
, "Markup should work properly after a blank line" =:
- unlines ["foo", "", "/bar/"] =?>
+ T.unlines ["foo", "", "/bar/"] =?>
(para $ text "foo") <> (para $ emph $ text "bar")
, "Inline math must stay within three lines" =:
- unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
+ T.unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?>
para ((math "a\nb\nc") <> softbreak <>
"$d" <> softbreak <> "e" <> softbreak <>
"f" <> softbreak <> "g$")
@@ -165,17 +171,17 @@ tests =
softbreak <> "emph/")
, "Sub- and superscript expressions" =:
- unlines [ "a_(a(b)(c)d)"
- , "e^(f(g)h)"
- , "i_(jk)l)"
- , "m^()n"
- , "o_{p{q{}r}}"
- , "s^{t{u}v}"
- , "w_{xy}z}"
- , "1^{}2"
- , "3_{{}}"
- , "4^(a(*b(c*)d))"
- ] =?>
+ T.unlines [ "a_(a(b)(c)d)"
+ , "e^(f(g)h)"
+ , "i_(jk)l)"
+ , "m^()n"
+ , "o_{p{q{}r}}"
+ , "s^{t{u}v}"
+ , "w_{xy}z}"
+ , "1^{}2"
+ , "3_{{}}"
+ , "4^(a(*b(c*)d))"
+ ] =?>
para (mconcat $ intersperse softbreak
[ "a" <> subscript "(a(b)(c)d)"
, "e" <> superscript "(f(g)h)"
@@ -202,17 +208,17 @@ tests =
(para $ image "sunrise.jpg" "" "")
, "Multiple images within a paragraph" =:
- unlines [ "[[file:sunrise.jpg]]"
- , "[[file:sunset.jpg]]"
- ] =?>
+ T.unlines [ "[[file:sunrise.jpg]]"
+ , "[[file:sunset.jpg]]"
+ ] =?>
(para $ (image "sunrise.jpg" "" "")
<> softbreak
<> (image "sunset.jpg" "" ""))
, "Image with html attributes" =:
- unlines [ "#+ATTR_HTML: :width 50%"
- , "[[file:guinea-pig.gif]]"
- ] =?>
+ T.unlines [ "#+ATTR_HTML: :width 50%"
+ , "[[file:guinea-pig.gif]]"
+ ] =?>
(para $ imageWith ("", [], [("width", "50%")]) "guinea-pig.gif" "" "")
]
@@ -334,6 +340,18 @@ tests =
}
in (para $ cite [citation] "cite:pandoc")
+ , "Org-ref simple citation with underscores" =:
+ "cite:pandoc_org_ref" =?>
+ let citation = Citation
+ { citationId = "pandoc_org_ref"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc_org_ref")
+
, "Org-ref simple citation succeeded by comma" =:
"cite:pandoc," =?>
let citation = Citation
@@ -346,6 +364,30 @@ tests =
}
in (para $ cite [citation] "cite:pandoc" <> str ",")
+ , "Org-ref simple citation succeeded by dot" =:
+ "cite:pandoc." =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc" <> str ".")
+
+ , "Org-ref simple citation succeeded by colon" =:
+ "cite:pandoc:" =?>
+ let citation = Citation
+ { citationId = "pandoc"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = AuthorInText
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [citation] "cite:pandoc" <> str ":")
+
, "Org-ref simple citep citation" =:
"citep:pandoc" =?>
let citation = Citation
@@ -469,6 +511,24 @@ tests =
, citationNoteNum = 0
, citationHash = 0}
in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
+
+ , "Macro" =:
+ T.unlines [ "#+MACRO: HELLO /Hello, $1/"
+ , "{{{HELLO(World)}}}"
+ ] =?>
+ para (emph "Hello, World")
+
+ , "Macro repeting its argument" =:
+ T.unlines [ "#+MACRO: HELLO $1$1"
+ , "{{{HELLO(moin)}}}"
+ ] =?>
+ para "moinmoin"
+
+ , "Macro called with too few arguments" =:
+ T.unlines [ "#+MACRO: HELLO Foo $1 $2 Bar"
+ , "{{{HELLO()}}}"
+ ] =?>
+ para "Foo Bar"
]
, testGroup "Meta Information" $
@@ -481,10 +541,10 @@ tests =
para "#-tag"
, "Comment surrounded by Text" =:
- unlines [ "Before"
- , "# Comment"
- , "After"
- ] =?>
+ T.unlines [ "Before"
+ , "# Comment"
+ , "After"
+ ] =?>
mconcat [ para "Before"
, para "After"
]
@@ -521,10 +581,10 @@ tests =
in Pandoc meta mempty
, "Properties drawer" =:
- unlines [ " :PROPERTIES:"
- , " :setting: foo"
- , " :END:"
- ] =?>
+ T.unlines [ " :PROPERTIES:"
+ , " :setting: foo"
+ , " :END:"
+ ] =?>
(mempty::Blocks)
, "LaTeX_headers options are translated to header-includes" =:
@@ -552,46 +612,46 @@ tests =
in Pandoc meta mempty
, "later meta definitions take precedence" =:
- unlines [ "#+AUTHOR: this will not be used"
- , "#+author: Max"
- ] =?>
+ T.unlines [ "#+AUTHOR: this will not be used"
+ , "#+author: Max"
+ ] =?>
let author = MetaInlines [Str "Max"]
meta = setMeta "author" (MetaList [author]) $ nullMeta
in Pandoc meta mempty
, "Logbook drawer" =:
- unlines [ " :LogBook:"
- , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]"
- , " :END:"
- ] =?>
+ T.unlines [ " :LogBook:"
+ , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]"
+ , " :END:"
+ ] =?>
(mempty::Blocks)
, "Drawer surrounded by text" =:
- unlines [ "Before"
- , ":PROPERTIES:"
- , ":END:"
- , "After"
- ] =?>
+ T.unlines [ "Before"
+ , ":PROPERTIES:"
+ , ":END:"
+ , "After"
+ ] =?>
para "Before" <> para "After"
, "Drawer markers must be the only text in the line" =:
- unlines [ " :LOGBOOK: foo"
- , " :END: bar"
- ] =?>
+ T.unlines [ " :LOGBOOK: foo"
+ , " :END: bar"
+ ] =?>
para (":LOGBOOK: foo" <> softbreak <> ":END: bar")
, "Drawers can be arbitrary" =:
- unlines [ ":FOO:"
- , "/bar/"
- , ":END:"
- ] =?>
+ T.unlines [ ":FOO:"
+ , "/bar/"
+ , ":END:"
+ ] =?>
divWith (mempty, ["FOO", "drawer"], mempty) (para $ emph "bar")
, "Anchor reference" =:
- unlines [ "<<link-here>> Target."
- , ""
- , "[[link-here][See here!]]"
- ] =?>
+ T.unlines [ "<<link-here>> Target."
+ , ""
+ , "[[link-here][See here!]]"
+ ] =?>
(para (spanWith ("link-here", [], []) mempty <> "Target.") <>
para (link "#link-here" "" ("See" <> space <> "here!")))
@@ -600,129 +660,148 @@ tests =
(para (emph $ "Where's" <> space <> "Wally?"))
, "Link to nonexistent anchor" =:
- unlines [ "<<link-here>> Target."
- , ""
- , "[[link$here][See here!]]"
- ] =?>
+ T.unlines [ "<<link-here>> Target."
+ , ""
+ , "[[link$here][See here!]]"
+ ] =?>
(para (spanWith ("link-here", [], []) mempty <> "Target.") <>
para (emph ("See" <> space <> "here!")))
, "Link abbreviation" =:
- unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
- , "[[wp:Org_mode][Wikipedia on Org-mode]]"
- ] =?>
+ T.unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s"
+ , "[[wp:Org_mode][Wikipedia on Org-mode]]"
+ ] =?>
(para (link "https://en.wikipedia.org/wiki/Org_mode" ""
("Wikipedia" <> space <> "on" <> space <> "Org-mode")))
, "Link abbreviation, defined after first use" =:
- unlines [ "[[zl:non-sense][Non-sense articles]]"
- , "#+LINK: zl http://zeitlens.com/tags/%s.html"
- ] =?>
+ T.unlines [ "[[zl:non-sense][Non-sense articles]]"
+ , "#+LINK: zl http://zeitlens.com/tags/%s.html"
+ ] =?>
(para (link "http://zeitlens.com/tags/non-sense.html" ""
("Non-sense" <> space <> "articles")))
, "Link abbreviation, URL encoded arguments" =:
- unlines [ "#+link: expl http://example.com/%h/foo"
- , "[[expl:Hello, World!][Moin!]]"
- ] =?>
+ T.unlines [ "#+link: expl http://example.com/%h/foo"
+ , "[[expl:Hello, World!][Moin!]]"
+ ] =?>
(para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!"))
, "Link abbreviation, append arguments" =:
- unlines [ "#+link: expl http://example.com/"
- , "[[expl:foo][bar]]"
- ] =?>
+ T.unlines [ "#+link: expl http://example.com/"
+ , "[[expl:foo][bar]]"
+ ] =?>
(para (link "http://example.com/foo" "" "bar"))
, testGroup "export options"
[ "disable simple sub/superscript syntax" =:
- unlines [ "#+OPTIONS: ^:nil"
- , "a^b"
- ] =?>
+ T.unlines [ "#+OPTIONS: ^:nil"
+ , "a^b"
+ ] =?>
para "a^b"
, "directly select drawers to be exported" =:
- unlines [ "#+OPTIONS: d:(\"IMPORTANT\")"
- , ":IMPORTANT:"
- , "23"
- , ":END:"
- , ":BORING:"
- , "very boring"
- , ":END:"
- ] =?>
+ T.unlines [ "#+OPTIONS: d:(\"IMPORTANT\")"
+ , ":IMPORTANT:"
+ , "23"
+ , ":END:"
+ , ":BORING:"
+ , "very boring"
+ , ":END:"
+ ] =?>
divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "23")
, "exclude drawers from being exported" =:
- unlines [ "#+OPTIONS: d:(not \"BORING\")"
- , ":IMPORTANT:"
- , "5"
- , ":END:"
- , ":BORING:"
- , "very boring"
- , ":END:"
- ] =?>
+ T.unlines [ "#+OPTIONS: d:(not \"BORING\")"
+ , ":IMPORTANT:"
+ , "5"
+ , ":END:"
+ , ":BORING:"
+ , "very boring"
+ , ":END:"
+ ] =?>
divWith (mempty, ["IMPORTANT", "drawer"], mempty) (para "5")
, "don't include archive trees" =:
- unlines [ "#+OPTIONS: arch:nil"
- , "* old :ARCHIVE:"
- ] =?>
+ T.unlines [ "#+OPTIONS: arch:nil"
+ , "* old :ARCHIVE:"
+ ] =?>
(mempty ::Blocks)
, "include complete archive trees" =:
- unlines [ "#+OPTIONS: arch:t"
- , "* old :ARCHIVE:"
- , " boring"
- ] =?>
- let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty
- in mconcat [ headerWith ("old", [], mempty) 1 ("old" <> tagSpan "ARCHIVE")
- , para "boring"
- ]
+ T.unlines [ "#+OPTIONS: arch:t"
+ , "* old :ARCHIVE:"
+ , " boring"
+ ] =?>
+ mconcat [ headerWith ("old", [], mempty) 1
+ ("old" <> space <> tagSpan "ARCHIVE")
+ , para "boring"
+ ]
, "include archive tree header only" =:
- unlines [ "#+OPTIONS: arch:headline"
- , "* old :ARCHIVE:"
- , " boring"
- ] =?>
- let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty
- in headerWith ("old", [], mempty) 1 ("old" <> tagSpan "ARCHIVE")
+ T.unlines [ "#+OPTIONS: arch:headline"
+ , "* old :ARCHIVE:"
+ , " boring"
+ ] =?>
+ headerWith ("old", [], mempty) 1 ("old" <> space <> tagSpan "ARCHIVE")
, "limit headline depth" =:
- unlines [ "#+OPTIONS: H:2"
- , "* section"
- , "** subsection"
- , "*** list item 1"
- , "*** list item 2"
- ] =?>
- mconcat [ headerWith ("section", [], []) 1 "section"
+ T.unlines [ "#+OPTIONS: H:2"
+ , "* top-level section"
+ , "** subsection"
+ , "*** list item 1"
+ , "*** list item 2"
+ ] =?>
+ mconcat [ headerWith ("top-level-section", [], []) 1 "top-level section"
, headerWith ("subsection", [], []) 2 "subsection"
, orderedList [ para "list item 1", para "list item 2" ]
]
+ , "turn all headlines into lists" =:
+ T.unlines [ "#+OPTIONS: H:0"
+ , "first block"
+ , "* top-level section 1"
+ , "** subsection"
+ , "* top-level section 2"
+ ] =?>
+ mconcat [ para "first block"
+ , orderedList
+ [ (para "top-level section 1" <>
+ orderedList [ para "subsection" ])
+ , para "top-level section 2" ]
+ ]
+
, "disable author export" =:
- unlines [ "#+OPTIONS: author:nil"
- , "#+AUTHOR: ShyGuy"
- ] =?>
+ T.unlines [ "#+OPTIONS: author:nil"
+ , "#+AUTHOR: ShyGuy"
+ ] =?>
Pandoc nullMeta mempty
, "disable creator export" =:
- unlines [ "#+OPTIONS: creator:nil"
- , "#+creator: The Architect"
- ] =?>
+ T.unlines [ "#+OPTIONS: creator:nil"
+ , "#+creator: The Architect"
+ ] =?>
Pandoc nullMeta mempty
, "disable email export" =:
- unlines [ "#+OPTIONS: email:nil"
- , "#+email: no-mail-please@example.com"
- ] =?>
+ T.unlines [ "#+OPTIONS: email:nil"
+ , "#+email: no-mail-please@example.com"
+ ] =?>
Pandoc nullMeta mempty
, "disable inclusion of todo keywords" =:
- unlines [ "#+OPTIONS: todo:nil"
- , "** DONE todo export"
- ] =?>
+ T.unlines [ "#+OPTIONS: todo:nil"
+ , "** DONE todo export"
+ ] =?>
headerWith ("todo-export", [], []) 2 "todo export"
+
+ , "remove tags from headlines" =:
+ T.unlines [ "#+OPTIONS: tags:nil"
+ , "* Headline :hello:world:"
+ ] =?>
+ headerWith ("headline", [], mempty) 1 "Headline"
]
]
@@ -743,10 +822,10 @@ tests =
("Third" <> space <> "Level" <> space <> "Headline")
, "Compact Headers with Paragraph" =:
- unlines [ "* First Level"
- , "** Second Level"
- , " Text"
- ] =?>
+ T.unlines [ "* First Level"
+ , "** Second Level"
+ , " Text"
+ ] =?>
mconcat [ headerWith ("first-level", [], [])
1
("First" <> space <> "Level")
@@ -757,12 +836,12 @@ tests =
]
, "Separated Headers with Paragraph" =:
- unlines [ "* First Level"
- , ""
- , "** Second Level"
- , ""
- , " Text"
- ] =?>
+ T.unlines [ "* First Level"
+ , ""
+ , "** Second Level"
+ , ""
+ , " Text"
+ ] =?>
mconcat [ headerWith ("first-level", [], [])
1
("First" <> space <> "Level")
@@ -773,10 +852,10 @@ tests =
]
, "Headers not preceded by a blank line" =:
- unlines [ "** eat dinner"
- , "Spaghetti and meatballs tonight."
- , "** walk dog"
- ] =?>
+ T.unlines [ "** eat dinner"
+ , "Spaghetti and meatballs tonight."
+ , "** walk dog"
+ ] =?>
mconcat [ headerWith ("eat-dinner", [], [])
2
("eat" <> space <> "dinner")
@@ -802,21 +881,21 @@ tests =
headerWith ("waiting-header", [], []) 1 "WAITING header"
, "Custom todo keywords" =:
- unlines [ "#+TODO: WAITING CANCELLED"
- , "* WAITING compile"
- , "* CANCELLED lunch"
- ] =?>
+ T.unlines [ "#+TODO: WAITING CANCELLED"
+ , "* WAITING compile"
+ , "* CANCELLED lunch"
+ ] =?>
let todoSpan = spanWith ("", ["todo", "WAITING"], []) "WAITING"
doneSpan = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED"
in headerWith ("compile", [], []) 1 (todoSpan <> space <> "compile")
<> headerWith ("lunch", [], []) 1 (doneSpan <> space <> "lunch")
, "Custom todo keywords with multiple done-states" =:
- unlines [ "#+TODO: WAITING | DONE CANCELLED "
- , "* WAITING compile"
- , "* CANCELLED lunch"
- , "* DONE todo-feature"
- ] =?>
+ T.unlines [ "#+TODO: WAITING | DONE CANCELLED "
+ , "* WAITING compile"
+ , "* CANCELLED lunch"
+ , "* DONE todo-feature"
+ ] =?>
let waiting = spanWith ("", ["todo", "WAITING"], []) "WAITING"
cancelled = spanWith ("", ["done", "CANCELLED"], []) "CANCELLED"
done = spanWith ("", ["done", "DONE"], []) "DONE"
@@ -826,31 +905,30 @@ tests =
]
, "Tagged headers" =:
- unlines [ "* Personal :PERSONAL:"
- , "** Call Mom :@PHONE:"
- , "** Call John :@PHONE:JOHN: "
- ] =?>
- let tagSpan t = spanWith ("", ["tag"], [("data-tag-name", t)]) mempty
- in mconcat [ headerWith ("personal", [], [])
- 1
- ("Personal" <> tagSpan "PERSONAL")
- , headerWith ("call-mom", [], [])
- 2
- ("Call Mom" <> tagSpan "@PHONE")
- , headerWith ("call-john", [], [])
- 2
- ("Call John" <> tagSpan "@PHONE" <> tagSpan "JOHN")
- ]
+ T.unlines [ "* Personal :PERSONAL:"
+ , "** Call Mom :@PHONE:"
+ , "** Call John :@PHONE:JOHN: "
+ ] =?>
+ mconcat [ headerWith ("personal", [], [])
+ 1
+ ("Personal " <> tagSpan "PERSONAL")
+ , headerWith ("call-mom", [], [])
+ 2
+ ("Call Mom " <> tagSpan "@PHONE")
+ , headerWith ("call-john", [], [])
+ 2
+ ("Call John " <> tagSpan "@PHONE" <> "\160" <> tagSpan "JOHN")
+ ]
, "Untagged header containing colons" =:
"* This: is not: tagged" =?>
headerWith ("this-is-not-tagged", [], []) 1 "This: is not: tagged"
, "Header starting with strokeout text" =:
- unlines [ "foo"
- , ""
- , "* +thing+ other thing"
- ] =?>
+ T.unlines [ "foo"
+ , ""
+ , "* +thing+ other thing"
+ ] =?>
mconcat [ para "foo"
, headerWith ("thing-other-thing", [], [])
1
@@ -858,11 +936,11 @@ tests =
]
, "Comment Trees" =:
- unlines [ "* COMMENT A comment tree"
- , " Not much going on here"
- , "** This will be dropped"
- , "* Comment tree above"
- ] =?>
+ T.unlines [ "* COMMENT A comment tree"
+ , " Not much going on here"
+ , "** This will be dropped"
+ , "* Comment tree above"
+ ] =?>
headerWith ("comment-tree-above", [], []) 1 "Comment tree above"
, "Nothing but a COMMENT header" =:
@@ -870,38 +948,38 @@ tests =
(mempty::Blocks)
, "Tree with :noexport:" =:
- unlines [ "* Should be ignored :archive:noexport:old:"
- , "** Old stuff"
- , " This is not going to be exported"
- ] =?>
+ T.unlines [ "* Should be ignored :archive:noexport:old:"
+ , "** Old stuff"
+ , " This is not going to be exported"
+ ] =?>
(mempty::Blocks)
, "Subtree with :noexport:" =:
- unlines [ "* Exported"
- , "** This isn't exported :noexport:"
- , "*** This neither"
- , "** But this is"
- ] =?>
+ T.unlines [ "* Exported"
+ , "** This isn't exported :noexport:"
+ , "*** This neither"
+ , "** But this is"
+ ] =?>
mconcat [ headerWith ("exported", [], []) 1 "Exported"
, headerWith ("but-this-is", [], []) 2 "But this is"
]
, "Preferences are treated as header attributes" =:
- unlines [ "* foo"
- , " :PROPERTIES:"
- , " :custom_id: fubar"
- , " :bar: baz"
- , " :END:"
- ] =?>
+ T.unlines [ "* foo"
+ , " :PROPERTIES:"
+ , " :custom_id: fubar"
+ , " :bar: baz"
+ , " :END:"
+ ] =?>
headerWith ("fubar", [], [("bar", "baz")]) 1 "foo"
, "Headers marked with a unnumbered property get a class of the same name" =:
- unlines [ "* Not numbered"
- , " :PROPERTIES:"
- , " :UNNUMBERED: t"
- , " :END:"
- ] =?>
+ T.unlines [ "* Not numbered"
+ , " :PROPERTIES:"
+ , " :UNNUMBERED: t"
+ , " :END:"
+ ] =?>
headerWith ("not-numbered", ["unnumbered"], []) 1 "Not numbered"
]
, "Paragraph starting with an asterisk" =:
@@ -909,23 +987,23 @@ tests =
para "*five"
, "Paragraph containing asterisk at beginning of line" =:
- unlines [ "lucky"
- , "*star"
- ] =?>
+ T.unlines [ "lucky"
+ , "*star"
+ ] =?>
para ("lucky" <> softbreak <> "*star")
, "Example block" =:
- unlines [ ": echo hello"
- , ": echo dear tester"
- ] =?>
+ T.unlines [ ": echo hello"
+ , ": echo dear tester"
+ ] =?>
codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n"
, "Example block surrounded by text" =:
- unlines [ "Greetings"
- , ": echo hello"
- , ": echo dear tester"
- , "Bye"
- ] =?>
+ T.unlines [ "Greetings"
+ , ": echo hello"
+ , ": echo dear tester"
+ , "Bye"
+ ] =?>
mconcat [ para "Greetings"
, codeBlockWith ("", ["example"], [])
"echo hello\necho dear tester\n"
@@ -933,81 +1011,81 @@ tests =
]
, "Horizontal Rule" =:
- unlines [ "before"
- , "-----"
- , "after"
- ] =?>
+ T.unlines [ "before"
+ , "-----"
+ , "after"
+ ] =?>
mconcat [ para "before"
, horizontalRule
, para "after"
]
, "Not a Horizontal Rule" =:
- "----- five dashes" =?>
- (para $ spcSep [ "-----", "five", "dashes" ])
+ "----- em and en dash" =?>
+ para "\8212\8211 em and en dash"
, "Comment Block" =:
- unlines [ "#+BEGIN_COMMENT"
- , "stuff"
- , "bla"
- , "#+END_COMMENT"] =?>
+ T.unlines [ "#+BEGIN_COMMENT"
+ , "stuff"
+ , "bla"
+ , "#+END_COMMENT"] =?>
(mempty::Blocks)
, testGroup "Figures" $
[ "Figure" =:
- unlines [ "#+caption: A very courageous man."
- , "#+name: goodguy"
- , "[[file:edward.jpg]]"
- ] =?>
+ T.unlines [ "#+caption: A very courageous man."
+ , "#+name: goodguy"
+ , "[[file:edward.jpg]]"
+ ] =?>
para (image "edward.jpg" "fig:goodguy" "A very courageous man.")
, "Figure with no name" =:
- unlines [ "#+caption: I've been through the desert on this"
- , "[[file:horse.png]]"
- ] =?>
+ T.unlines [ "#+caption: I've been through the desert on this"
+ , "[[file:horse.png]]"
+ ] =?>
para (image "horse.png" "fig:" "I've been through the desert on this")
, "Figure with `fig:` prefix in name" =:
- unlines [ "#+caption: Used as a metapher in evolutionary biology."
- , "#+name: fig:redqueen"
- , "[[./the-red-queen.jpg]]"
- ] =?>
+ T.unlines [ "#+caption: Used as a metapher in evolutionary biology."
+ , "#+name: fig:redqueen"
+ , "[[./the-red-queen.jpg]]"
+ ] =?>
para (image "./the-red-queen.jpg" "fig:redqueen"
"Used as a metapher in evolutionary biology.")
, "Figure with HTML attributes" =:
- unlines [ "#+CAPTION: mah brain just explodid"
- , "#+NAME: lambdacat"
- , "#+ATTR_HTML: :style color: blue :role button"
- , "[[file:lambdacat.jpg]]"
- ] =?>
+ T.unlines [ "#+CAPTION: mah brain just explodid"
+ , "#+NAME: lambdacat"
+ , "#+ATTR_HTML: :style color: blue :role button"
+ , "[[file:lambdacat.jpg]]"
+ ] =?>
let kv = [("style", "color: blue"), ("role", "button")]
name = "fig:lambdacat"
caption = "mah brain just explodid"
in para (imageWith (mempty, mempty, kv) "lambdacat.jpg" name caption)
, "Labelled figure" =:
- unlines [ "#+CAPTION: My figure"
- , "#+LABEL: fig:myfig"
- , "[[file:blub.png]]"
- ] =?>
+ T.unlines [ "#+CAPTION: My figure"
+ , "#+LABEL: fig:myfig"
+ , "[[file:blub.png]]"
+ ] =?>
let attr = ("fig:myfig", mempty, mempty)
in para (imageWith attr "blub.png" "fig:" "My figure")
, "Figure with empty caption" =:
- unlines [ "#+CAPTION:"
- , "[[file:guess.jpg]]"
- ] =?>
+ T.unlines [ "#+CAPTION:"
+ , "[[file:guess.jpg]]"
+ ] =?>
para (image "guess.jpg" "fig:" "")
]
, "Footnote" =:
- unlines [ "A footnote[1]"
- , ""
- , "[1] First paragraph"
- , ""
- , "second paragraph"
- ] =?>
+ T.unlines [ "A footnote[1]"
+ , ""
+ , "[1] First paragraph"
+ , ""
+ , "second paragraph"
+ ] =?>
para (mconcat
[ "A", space, "footnote"
, note $ mconcat [ para ("First" <> space <> "paragraph")
@@ -1016,12 +1094,12 @@ tests =
])
, "Two footnotes" =:
- unlines [ "Footnotes[fn:1][fn:2]"
- , ""
- , "[fn:1] First note."
- , ""
- , "[fn:2] Second note."
- ] =?>
+ T.unlines [ "Footnotes[fn:1][fn:2]"
+ , ""
+ , "[fn:1] First note."
+ , ""
+ , "[fn:2] Second note."
+ ] =?>
para (mconcat
[ "Footnotes"
, note $ para ("First" <> space <> "note.")
@@ -1029,32 +1107,32 @@ tests =
])
, "Emphasized text before footnote" =:
- unlines [ "/text/[fn:1]"
- , ""
- , "[fn:1] unicorn"
- ] =?>
+ T.unlines [ "/text/[fn:1]"
+ , ""
+ , "[fn:1] unicorn"
+ ] =?>
para (mconcat
[ emph "text"
, note . para $ "unicorn"
])
, "Footnote that starts with emphasized text" =:
- unlines [ "text[fn:1]"
- , ""
- , "[fn:1] /emphasized/"
- ] =?>
+ T.unlines [ "text[fn:1]"
+ , ""
+ , "[fn:1] /emphasized/"
+ ] =?>
para (mconcat
[ "text"
, note . para $ emph "emphasized"
])
, "Footnote followed by header" =:
- unlines [ "Another note[fn:yay]"
- , ""
- , "[fn:yay] This is great!"
- , ""
- , "** Headline"
- ] =?>
+ T.unlines [ "Another note[fn:yay]"
+ , ""
+ , "[fn:yay] This is great!"
+ , ""
+ , "** Headline"
+ ] =?>
mconcat
[ para (mconcat
[ "Another", space, "note"
@@ -1066,43 +1144,43 @@ tests =
, testGroup "Lists" $
[ "Simple Bullet Lists" =:
- ("- Item1\n" ++
+ ("- Item1\n" <>
"- Item2\n") =?>
bulletList [ plain "Item1"
, plain "Item2"
]
, "Indented Bullet Lists" =:
- (" - Item1\n" ++
+ (" - Item1\n" <>
" - Item2\n") =?>
bulletList [ plain "Item1"
, plain "Item2"
]
, "Unindented *" =:
- ("- Item1\n" ++
+ ("- Item1\n" <>
"* Item2\n") =?>
bulletList [ plain "Item1"
] <>
headerWith ("item2", [], []) 1 "Item2"
, "Multi-line Bullet Lists" =:
- ("- *Fat\n" ++
- " Tony*\n" ++
- "- /Sideshow\n" ++
+ ("- *Fat\n" <>
+ " Tony*\n" <>
+ "- /Sideshow\n" <>
" Bob/") =?>
bulletList [ plain $ strong ("Fat" <> softbreak <> "Tony")
, plain $ emph ("Sideshow" <> softbreak <> "Bob")
]
, "Nested Bullet Lists" =:
- ("- Discovery\n" ++
- " + One More Time\n" ++
- " + Harder, Better, Faster, Stronger\n" ++
- "- Homework\n" ++
- " + Around the World\n"++
- "- Human After All\n" ++
- " + Technologic\n" ++
+ ("- Discovery\n" <>
+ " + One More Time\n" <>
+ " + Harder, Better, Faster, Stronger\n" <>
+ "- Homework\n" <>
+ " + Around the World\n"<>
+ "- Human After All\n" <>
+ " + Technologic\n" <>
" + Robot Rock\n") =?>
bulletList [ mconcat
[ plain "Discovery"
@@ -1158,7 +1236,7 @@ tests =
]
, "Simple Ordered List" =:
- ("1. Item1\n" ++
+ ("1. Item1\n" <>
"2. Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
@@ -1167,7 +1245,7 @@ tests =
in orderedListWith listStyle listStructure
, "Simple Ordered List with Parens" =:
- ("1) Item1\n" ++
+ ("1) Item1\n" <>
"2) Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
@@ -1176,7 +1254,7 @@ tests =
in orderedListWith listStyle listStructure
, "Indented Ordered List" =:
- (" 1. Item1\n" ++
+ (" 1. Item1\n" <>
" 2. Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
@@ -1185,11 +1263,11 @@ tests =
in orderedListWith listStyle listStructure
, "Nested Ordered Lists" =:
- ("1. One\n" ++
- " 1. One-One\n" ++
- " 2. One-Two\n" ++
- "2. Two\n" ++
- " 1. Two-One\n"++
+ ("1. One\n" <>
+ " 1. One-One\n" <>
+ " 2. One-Two\n" <>
+ "2. Two\n" <>
+ " 1. Two-One\n"<>
" 2. Two-Two\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ mconcat
@@ -1208,25 +1286,25 @@ tests =
in orderedListWith listStyle listStructure
, "Ordered List in Bullet List" =:
- ("- Emacs\n" ++
+ ("- Emacs\n" <>
" 1. Org\n") =?>
bulletList [ (plain "Emacs") <>
(orderedList [ plain "Org"])
]
, "Bullet List in Ordered List" =:
- ("1. GNU\n" ++
+ ("1. GNU\n" <>
" - Freedom\n") =?>
orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ]
, "Definition List" =:
- unlines [ "- PLL :: phase-locked loop"
- , "- TTL ::"
- , " transistor-transistor logic"
- , "- PSK :: phase-shift keying"
- , ""
- , " a digital modulation scheme"
- ] =?>
+ T.unlines [ "- PLL :: phase-locked loop"
+ , "- TTL ::"
+ , " transistor-transistor logic"
+ , "- PSK :: phase-shift keying"
+ , ""
+ , " a digital modulation scheme"
+ ] =?>
definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ])
, ("TTL", [ plain $ "transistor-transistor" <> space <>
"logic" ])
@@ -1241,11 +1319,11 @@ tests =
" - Elijah Wood :: He plays Frodo" =?>
definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])]
, "Compact definition list" =:
- unlines [ "- ATP :: adenosine 5' triphosphate"
- , "- DNA :: deoxyribonucleic acid"
- , "- PCR :: polymerase chain reaction"
- , ""
- ] =?>
+ T.unlines [ "- ATP :: adenosine 5' triphosphate"
+ , "- DNA :: deoxyribonucleic acid"
+ , "- PCR :: polymerase chain reaction"
+ , ""
+ ] =?>
definitionList
[ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ])
, ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ])
@@ -1267,21 +1345,21 @@ tests =
bulletList [ plain "std::cout" ]
, "Loose bullet list" =:
- unlines [ "- apple"
- , ""
- , "- orange"
- , ""
- , "- peach"
- ] =?>
+ T.unlines [ "- apple"
+ , ""
+ , "- orange"
+ , ""
+ , "- peach"
+ ] =?>
bulletList [ para "apple"
, para "orange"
, para "peach"
]
, "Recognize preceding paragraphs in non-list contexts" =:
- unlines [ "CLOSED: [2015-10-19 Mon 15:03]"
- , "- Note taken on [2015-10-19 Mon 13:24]"
- ] =?>
+ T.unlines [ "CLOSED: [2015-10-19 Mon 15:03]"
+ , "- Note taken on [2015-10-19 Mon 13:24]"
+ ] =?>
mconcat [ para "CLOSED: [2015-10-19 Mon 15:03]"
, bulletList [ plain "Note taken on [2015-10-19 Mon 13:24]" ]
]
@@ -1297,10 +1375,10 @@ tests =
simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
, "Multi line table" =:
- unlines [ "| One |"
- , "| Two |"
- , "| Three |"
- ] =?>
+ T.unlines [ "| One |"
+ , "| Two |"
+ , "| Three |"
+ ] =?>
simpleTable' 1 mempty
[ [ plain "One" ]
, [ plain "Two" ]
@@ -1312,10 +1390,10 @@ tests =
simpleTable' 1 mempty [[mempty]]
, "Glider Table" =:
- unlines [ "| 1 | 0 | 0 |"
- , "| 0 | 1 | 1 |"
- , "| 1 | 1 | 0 |"
- ] =?>
+ T.unlines [ "| 1 | 0 | 0 |"
+ , "| 0 | 1 | 1 |"
+ , "| 1 | 1 | 0 |"
+ ] =?>
simpleTable' 3 mempty
[ [ plain "1", plain "0", plain "0" ]
, [ plain "0", plain "1", plain "1" ]
@@ -1323,42 +1401,42 @@ tests =
]
, "Table between Paragraphs" =:
- unlines [ "Before"
- , "| One | Two |"
- , "After"
- ] =?>
+ T.unlines [ "Before"
+ , "| One | Two |"
+ , "After"
+ ] =?>
mconcat [ para "Before"
, simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
, para "After"
]
, "Table with Header" =:
- unlines [ "| Species | Status |"
- , "|--------------+--------------|"
- , "| cervisiae | domesticated |"
- , "| paradoxus | wild |"
- ] =?>
+ T.unlines [ "| Species | Status |"
+ , "|--------------+--------------|"
+ , "| cervisiae | domesticated |"
+ , "| paradoxus | wild |"
+ ] =?>
simpleTable [ plain "Species", plain "Status" ]
[ [ plain "cervisiae", plain "domesticated" ]
, [ plain "paradoxus", plain "wild" ]
]
, "Table with final hline" =:
- unlines [ "| cervisiae | domesticated |"
- , "| paradoxus | wild |"
- , "|--------------+--------------|"
- ] =?>
+ T.unlines [ "| cervisiae | domesticated |"
+ , "| paradoxus | wild |"
+ , "|--------------+--------------|"
+ ] =?>
simpleTable' 2 mempty
[ [ plain "cervisiae", plain "domesticated" ]
, [ plain "paradoxus", plain "wild" ]
]
, "Table in a box" =:
- unlines [ "|---------|---------|"
- , "| static | Haskell |"
- , "| dynamic | Lisp |"
- , "|---------+---------|"
- ] =?>
+ T.unlines [ "|---------|---------|"
+ , "| static | Haskell |"
+ , "| dynamic | Lisp |"
+ , "|---------+---------|"
+ ] =?>
simpleTable' 2 mempty
[ [ plain "static", plain "Haskell" ]
, [ plain "dynamic", plain "Lisp" ]
@@ -1369,18 +1447,18 @@ tests =
simpleTable' 3 mempty [[mempty, mempty, plain "c"]]
, "Table with empty rows" =:
- unlines [ "| first |"
- , "| |"
- , "| third |"
- ] =?>
+ T.unlines [ "| first |"
+ , "| |"
+ , "| third |"
+ ] =?>
simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]]
, "Table with alignment row" =:
- unlines [ "| Numbers | Text | More |"
- , "| <c> | <r> | |"
- , "| 1 | One | foo |"
- , "| 2 | Two | bar |"
- ] =?>
+ T.unlines [ "| Numbers | Text | More |"
+ , "| <c> | <r> | |"
+ , "| 1 | One | foo |"
+ , "| 2 | Two | bar |"
+ ] =?>
table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
[]
[ [ plain "Numbers", plain "Text", plain "More" ]
@@ -1397,12 +1475,12 @@ tests =
simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ]
, "Table with differing row lengths" =:
- unlines [ "| Numbers | Text "
- , "|-"
- , "| <c> | <r> |"
- , "| 1 | One | foo |"
- , "| 2"
- ] =?>
+ T.unlines [ "| Numbers | Text "
+ , "|-"
+ , "| <c> | <r> |"
+ , "| 1 | One | foo |"
+ , "| 2"
+ ] =?>
table "" (zip [AlignCenter, AlignRight] [0, 0])
[ plain "Numbers", plain "Text" ]
[ [ plain "1" , plain "One" , plain "foo" ]
@@ -1410,10 +1488,10 @@ tests =
]
, "Table with caption" =:
- unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
- , "| x | 6 |"
- , "| 9 | 42 |"
- ] =?>
+ T.unlines [ "#+CAPTION: Hitchhiker's Multiplication Table"
+ , "| x | 6 |"
+ , "| 9 | 42 |"
+ ] =?>
table "Hitchhiker's Multiplication Table"
[(AlignDefault, 0), (AlignDefault, 0)]
[]
@@ -1424,59 +1502,59 @@ tests =
, testGroup "Blocks and fragments"
[ "Source block" =:
- unlines [ " #+BEGIN_SRC haskell"
- , " main = putStrLn greeting"
- , " where greeting = \"moin\""
- , " #+END_SRC" ] =?>
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , " #+END_SRC" ] =?>
let attr' = ("", ["haskell"], [])
- code' = "main = putStrLn greeting\n" ++
+ code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Source block with indented code" =:
- unlines [ " #+BEGIN_SRC haskell"
- , " main = putStrLn greeting"
- , " where greeting = \"moin\""
- , " #+END_SRC" ] =?>
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"moin\""
+ , " #+END_SRC" ] =?>
let attr' = ("", ["haskell"], [])
- code' = "main = putStrLn greeting\n" ++
+ code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Source block with tab-indented code" =:
- unlines [ "\t#+BEGIN_SRC haskell"
- , "\tmain = putStrLn greeting"
- , "\t where greeting = \"moin\""
- , "\t#+END_SRC" ] =?>
+ T.unlines [ "\t#+BEGIN_SRC haskell"
+ , "\tmain = putStrLn greeting"
+ , "\t where greeting = \"moin\""
+ , "\t#+END_SRC" ] =?>
let attr' = ("", ["haskell"], [])
- code' = "main = putStrLn greeting\n" ++
+ code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlockWith attr' code'
, "Empty source block" =:
- unlines [ " #+BEGIN_SRC haskell"
- , " #+END_SRC" ] =?>
+ T.unlines [ " #+BEGIN_SRC haskell"
+ , " #+END_SRC" ] =?>
let attr' = ("", ["haskell"], [])
code' = ""
in codeBlockWith attr' code'
, "Source block between paragraphs" =:
- unlines [ "Low German greeting"
- , " #+BEGIN_SRC haskell"
- , " main = putStrLn greeting"
- , " where greeting = \"Moin!\""
- , " #+END_SRC" ] =?>
+ T.unlines [ "Low German greeting"
+ , " #+BEGIN_SRC haskell"
+ , " main = putStrLn greeting"
+ , " where greeting = \"Moin!\""
+ , " #+END_SRC" ] =?>
let attr' = ("", ["haskell"], [])
- code' = "main = putStrLn greeting\n" ++
+ code' = "main = putStrLn greeting\n" <>
" where greeting = \"Moin!\"\n"
in mconcat [ para $ spcSep [ "Low", "German", "greeting" ]
, codeBlockWith attr' code'
]
, "Source block with babel arguments" =:
- unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
- , "(progn (message \"Hello, World!\")"
- , " (+ 23 42))"
- , "#+END_SRC" ] =?>
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC" ] =?>
let classes = [ "commonlisp" ] -- as kate doesn't know emacs-lisp syntax
params = [ ("data-org-language", "emacs-lisp")
, ("exports", "both")
@@ -1486,13 +1564,13 @@ tests =
in codeBlockWith ("", classes, params) code'
, "Source block with results and :exports both" =:
- unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
- , "(progn (message \"Hello, World!\")"
- , " (+ 23 42))"
- , "#+END_SRC"
- , ""
- , "#+RESULTS:"
- , ": 65"] =?>
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports both"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65"] =?>
let classes = [ "commonlisp" ]
params = [ ("data-org-language", "emacs-lisp")
, ("exports", "both")
@@ -1505,13 +1583,13 @@ tests =
codeBlockWith ("", ["example"], []) results'
, "Source block with results and :exports code" =:
- unlines [ "#+BEGIN_SRC emacs-lisp :exports code"
- , "(progn (message \"Hello, World!\")"
- , " (+ 23 42))"
- , "#+END_SRC"
- , ""
- , "#+RESULTS:"
- , ": 65" ] =?>
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports code"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
let classes = [ "commonlisp" ]
params = [ ("data-org-language", "emacs-lisp")
, ("exports", "code")
@@ -1521,87 +1599,87 @@ tests =
in codeBlockWith ("", classes, params) code'
, "Source block with results and :exports results" =:
- unlines [ "#+BEGIN_SRC emacs-lisp :exports results"
- , "(progn (message \"Hello, World!\")"
- , " (+ 23 42))"
- , "#+END_SRC"
- , ""
- , "#+RESULTS:"
- , ": 65" ] =?>
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports results"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
let results' = "65\n"
in codeBlockWith ("", ["example"], []) results'
, "Source block with results and :exports none" =:
- unlines [ "#+BEGIN_SRC emacs-lisp :exports none"
- , "(progn (message \"Hello, World!\")"
- , " (+ 23 42))"
- , "#+END_SRC"
- , ""
- , "#+RESULTS:"
- , ": 65" ] =?>
+ T.unlines [ "#+BEGIN_SRC emacs-lisp :exports none"
+ , "(progn (message \"Hello, World!\")"
+ , " (+ 23 42))"
+ , "#+END_SRC"
+ , ""
+ , "#+RESULTS:"
+ , ": 65" ] =?>
(mempty :: Blocks)
, "Source block with toggling header arguments" =:
- unlines [ "#+BEGIN_SRC sh :noeval"
- , "echo $HOME"
- , "#+END_SRC"
- ] =?>
+ T.unlines [ "#+BEGIN_SRC sh :noeval"
+ , "echo $HOME"
+ , "#+END_SRC"
+ ] =?>
let classes = [ "bash" ]
params = [ ("data-org-language", "sh"), ("noeval", "yes") ]
in codeBlockWith ("", classes, params) "echo $HOME\n"
, "Source block with line number switch" =:
- unlines [ "#+BEGIN_SRC sh -n 10"
- , ":() { :|:& };:"
- , "#+END_SRC"
- ] =?>
+ T.unlines [ "#+BEGIN_SRC sh -n 10"
+ , ":() { :|:& };:"
+ , "#+END_SRC"
+ ] =?>
let classes = [ "bash", "numberLines" ]
params = [ ("data-org-language", "sh"), ("startFrom", "10") ]
in codeBlockWith ("", classes, params) ":() { :|:& };:\n"
, "Source block with multi-word parameter values" =:
- unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng "
- , "digraph { id [label=\"ID\"] }"
- , "#+END_SRC"
- ] =?>
+ T.unlines [ "#+BEGIN_SRC dot :cmdline -Kdot -Tpng "
+ , "digraph { id [label=\"ID\"] }"
+ , "#+END_SRC"
+ ] =?>
let classes = [ "dot" ]
params = [ ("cmdline", "-Kdot -Tpng") ]
in codeBlockWith ("", classes, params) "digraph { id [label=\"ID\"] }\n"
, "Example block" =:
- unlines [ "#+begin_example"
- , "A chosen representation of"
- , "a rule."
- , "#+eND_exAMPle"
- ] =?>
+ T.unlines [ "#+begin_example"
+ , "A chosen representation of"
+ , "a rule."
+ , "#+eND_exAMPle"
+ ] =?>
codeBlockWith ("", ["example"], [])
"A chosen representation of\na rule.\n"
, "HTML block" =:
- unlines [ "#+BEGIN_HTML"
- , "<aside>HTML5 is pretty nice.</aside>"
- , "#+END_HTML"
- ] =?>
+ T.unlines [ "#+BEGIN_HTML"
+ , "<aside>HTML5 is pretty nice.</aside>"
+ , "#+END_HTML"
+ ] =?>
rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
, "Quote block" =:
- unlines [ "#+BEGIN_QUOTE"
- , "/Niemand/ hat die Absicht, eine Mauer zu errichten!"
- , "#+END_QUOTE"
- ] =?>
+ T.unlines [ "#+BEGIN_QUOTE"
+ , "/Niemand/ hat die Absicht, eine Mauer zu errichten!"
+ , "#+END_QUOTE"
+ ] =?>
blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
, "eine", "Mauer", "zu", "errichten!"
]))
, "Verse block" =:
- unlines [ "The first lines of Goethe's /Faust/:"
- , "#+begin_verse"
- , "Habe nun, ach! Philosophie,"
- , "Juristerei und Medizin,"
- , "Und leider auch Theologie!"
- , "Durchaus studiert, mit heißem Bemühn."
- , "#+end_verse"
- ] =?>
+ T.unlines [ "The first lines of Goethe's /Faust/:"
+ , "#+begin_verse"
+ , "Habe nun, ach! Philosophie,"
+ , "Juristerei und Medizin,"
+ , "Und leider auch Theologie!"
+ , "Durchaus studiert, mit heißem Bemühn."
+ , "#+end_verse"
+ ] =?>
mconcat
[ para $ spcSep [ "The", "first", "lines", "of"
, "Goethe's", emph "Faust" <> ":"]
@@ -1614,27 +1692,27 @@ tests =
]
, "Verse block with blank lines" =:
- unlines [ "#+BEGIN_VERSE"
- , "foo"
- , ""
- , "bar"
- , "#+END_VERSE"
- ] =?>
+ T.unlines [ "#+BEGIN_VERSE"
+ , "foo"
+ , ""
+ , "bar"
+ , "#+END_VERSE"
+ ] =?>
lineBlock [ "foo", mempty, "bar" ]
, "Verse block with varying indentation" =:
- unlines [ "#+BEGIN_VERSE"
- , " hello darkness"
- , "my old friend"
- , "#+END_VERSE"
- ] =?>
+ T.unlines [ "#+BEGIN_VERSE"
+ , " hello darkness"
+ , "my old friend"
+ , "#+END_VERSE"
+ ] =?>
lineBlock [ "\160\160hello darkness", "my old friend" ]
, "Raw block LaTeX" =:
- unlines [ "#+BEGIN_LaTeX"
- , "The category $\\cat{Set}$ is adhesive."
- , "#+END_LaTeX"
- ] =?>
+ T.unlines [ "#+BEGIN_LaTeX"
+ , "The category $\\cat{Set}$ is adhesive."
+ , "#+END_LaTeX"
+ ] =?>
rawBlock "latex" "The category $\\cat{Set}$ is adhesive.\n"
, "Raw LaTeX line" =:
@@ -1650,24 +1728,24 @@ tests =
rawBlock "html" "<aside>not important</aside>"
, "Export block HTML" =:
- unlines [ "#+BEGIN_export html"
- , "<samp>Hello, World!</samp>"
- , "#+END_export"
- ] =?>
+ T.unlines [ "#+BEGIN_export html"
+ , "<samp>Hello, World!</samp>"
+ , "#+END_export"
+ ] =?>
rawBlock "html" "<samp>Hello, World!</samp>\n"
, "LaTeX fragment" =:
- unlines [ "\\begin{equation}"
- , "X_i = \\begin{cases}"
- , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
- , " C_{\\alpha(i)} & \\text{otherwise}"
- , " \\end{cases}"
- , "\\end{equation}"
- ] =?>
+ T.unlines [ "\\begin{equation}"
+ , "X_i = \\begin{cases}"
+ , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
+ , " C_{\\alpha(i)} & \\text{otherwise}"
+ , " \\end{cases}"
+ , "\\end{equation}"
+ ] =?>
rawBlock "latex"
(unlines [ "\\begin{equation}"
, "X_i = \\begin{cases}"
- , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" ++
+ , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <>
" \\alpha(i)\\\\"
, " C_{\\alpha(i)} & \\text{otherwise}"
, " \\end{cases}"
@@ -1675,13 +1753,13 @@ tests =
])
, "Code block with caption" =:
- unlines [ "#+CAPTION: Functor laws in Haskell"
- , "#+NAME: functor-laws"
- , "#+BEGIN_SRC haskell"
- , "fmap id = id"
- , "fmap (p . q) = (fmap p) . (fmap q)"
- , "#+END_SRC"
- ] =?>
+ T.unlines [ "#+CAPTION: Functor laws in Haskell"
+ , "#+NAME: functor-laws"
+ , "#+BEGIN_SRC haskell"
+ , "fmap id = id"
+ , "fmap (p . q) = (fmap p) . (fmap q)"
+ , "#+END_SRC"
+ ] =?>
divWith
nullAttr
(mappend
@@ -1693,28 +1771,28 @@ tests =
])))
, "Convert blank lines in blocks to single newlines" =:
- unlines [ "#+begin_html"
- , ""
- , "<span>boring</span>"
- , ""
- , "#+end_html"
- ] =?>
+ T.unlines [ "#+begin_html"
+ , ""
+ , "<span>boring</span>"
+ , ""
+ , "#+end_html"
+ ] =?>
rawBlock "html" "\n<span>boring</span>\n\n"
, "Accept `ATTR_HTML` attributes for generic block" =:
- unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code"
- , "#+BEGIN_TEST"
- , "nonsense"
- , "#+END_TEST"
- ] =?>
+ T.unlines [ "#+ATTR_HTML: :title hello, world :id test :class fun code"
+ , "#+BEGIN_TEST"
+ , "nonsense"
+ , "#+END_TEST"
+ ] =?>
let attr = ("test", ["fun", "code", "TEST"], [("title", "hello, world")])
in divWith attr (para "nonsense")
, "Non-letter chars in source block parameters" =:
- unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich"
- , "code body"
- , "#+END_SRC"
- ] =?>
+ T.unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich"
+ , "code body"
+ , "#+END_SRC"
+ ] =?>
let params = [ ("data-org-language", "C")
, ("tangle", "xxxx.c")
, ("city", "Zürich")
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index 7f67ee742..cbca1564f 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -2,25 +2,27 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Tests.Readers.RST (tests) where
+import Data.Text (Text)
+import qualified Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
-rst :: String -> Pandoc
+rst :: Text -> Pandoc
rst = purely $ readRST def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
- => String -> (String, c) -> TestTree
+ => String -> (Text, c) -> TestTree
(=:) = test rst
tests :: [TestTree]
tests = [ "line block with blank line" =:
"| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ]
, testGroup "field list"
- [ "general" =: unlines
+ [ "general" =: T.unlines
[ "para"
, ""
, ":Hostname: media08"
@@ -44,7 +46,7 @@ tests = [ "line block with blank line" =:
, (text "Parameter i", [para "integer"])
, (str "Final", [para "item\non two lines"])
])
- , "metadata" =: unlines
+ , "metadata" =: T.unlines
[ "====="
, "Title"
, "====="
@@ -58,7 +60,7 @@ tests = [ "line block with blank line" =:
$ setMeta "title" ("Title" :: Inlines)
$ setMeta "subtitle" ("Subtitle" :: Inlines)
$ doc mempty )
- , "with inline markup" =: unlines
+ , "with inline markup" =: T.unlines
[ ":*Date*: today"
, ""
, ".."
@@ -80,7 +82,7 @@ tests = [ "line block with blank line" =:
])
]
, "URLs with following punctuation" =:
- ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" ++
+ ("http://google.com, http://yahoo.com; http://foo.bar.baz.\n" <>
"http://foo.bar/baz_(bam) (http://foo.bar)") =?>
para (link "http://google.com" "" "http://google.com" <> ", " <>
link "http://yahoo.com" "" "http://yahoo.com" <> "; " <>
@@ -89,10 +91,10 @@ tests = [ "line block with blank line" =:
link "http://foo.bar/baz_(bam)" "" "http://foo.bar/baz_(bam)"
<> " (" <> link "http://foo.bar" "" "http://foo.bar" <> ")")
, "Reference names with special characters" =:
- ("A-1-B_2_C:3:D+4+E.5.F_\n\n" ++
+ ("A-1-B_2_C:3:D+4+E.5.F_\n\n" <>
".. _A-1-B_2_C:3:D+4+E.5.F: https://example.com\n") =?>
para (link "https://example.com" "" "A-1-B_2_C:3:D+4+E.5.F")
- , "Code directive with class and number-lines" =: unlines
+ , "Code directive with class and number-lines" =: T.unlines
[ ".. code::python"
, " :number-lines: 34"
, " :class: class1 class2 class3"
@@ -107,7 +109,7 @@ tests = [ "line block with blank line" =:
)
"def func(x):\n return y"
)
- , "Code directive with number-lines, no line specified" =: unlines
+ , "Code directive with number-lines, no line specified" =: T.unlines
[ ".. code::python"
, " :number-lines: "
, ""
@@ -122,7 +124,7 @@ tests = [ "line block with blank line" =:
"def func(x):\n return y"
)
, testGroup "literal / line / code blocks"
- [ "indented literal block" =: unlines
+ [ "indented literal block" =: T.unlines
[ "::"
, ""
, " block quotes"
@@ -163,7 +165,7 @@ tests = [ "line block with blank line" =:
, "unknown role" =: ":unknown:`text`" =?> para (str "text")
]
, testGroup "footnotes"
- [ "remove space before note" =: unlines
+ [ "remove space before note" =: T.unlines
[ "foo [1]_"
, ""
, ".. [1]"
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index f6fa4f989..580815279 100644
--- a/test/Tests/Readers/Txt2Tags.hs
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -2,6 +2,8 @@
module Tests.Readers.Txt2Tags (tests) where
import Data.List (intersperse)
+import Data.Text (Text)
+import qualified Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -9,7 +11,7 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Class
-t2t :: String -> Pandoc
+t2t :: Text -> Pandoc
-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
t2t = purely $ \s -> do
putCommonState
@@ -20,7 +22,7 @@ t2t = purely $ \s -> do
infix 4 =:
(=:) :: ToString c
- => String -> (String, c) -> TestTree
+ => String -> (Text, c) -> TestTree
(=:) = test t2t
spcSep :: [Inlines] -> Inlines
@@ -154,7 +156,7 @@ tests =
"== header ==[lab/el]" =?>
para (text "== header ==[lab/el]")
, "Headers not preceded by a blank line" =:
- unlines [ "++ eat dinner ++"
+ T.unlines [ "++ eat dinner ++"
, "Spaghetti and meatballs tonight."
, "== walk dog =="
] =?>
@@ -168,16 +170,16 @@ tests =
para "=five"
, "Paragraph containing asterisk at beginning of line" =:
- unlines [ "lucky"
+ T.unlines [ "lucky"
, "*star"
] =?>
para ("lucky" <> softbreak <> "*star")
, "Horizontal Rule" =:
- unlines [ "before"
- , replicate 20 '-'
- , replicate 20 '='
- , replicate 20 '_'
+ T.unlines [ "before"
+ , T.replicate 20 "-"
+ , T.replicate 20 "="
+ , T.replicate 20 "_"
, "after"
] =?>
mconcat [ para "before"
@@ -188,7 +190,7 @@ tests =
]
, "Comment Block" =:
- unlines [ "%%%"
+ T.unlines [ "%%%"
, "stuff"
, "bla"
, "%%%"] =?>
@@ -199,14 +201,14 @@ tests =
, testGroup "Lists" $
[ "Simple Bullet Lists" =:
- ("- Item1\n" ++
+ ("- Item1\n" <>
"- Item2\n") =?>
bulletList [ plain "Item1"
, plain "Item2"
]
, "Indented Bullet Lists" =:
- (" - Item1\n" ++
+ (" - Item1\n" <>
" - Item2\n") =?>
bulletList [ plain "Item1"
, plain "Item2"
@@ -215,13 +217,13 @@ tests =
, "Nested Bullet Lists" =:
- ("- Discovery\n" ++
- " + One More Time\n" ++
- " + Harder, Better, Faster, Stronger\n" ++
- "- Homework\n" ++
- " + Around the World\n"++
- "- Human After All\n" ++
- " + Technologic\n" ++
+ ("- Discovery\n" <>
+ " + One More Time\n" <>
+ " + Harder, Better, Faster, Stronger\n" <>
+ "- Homework\n" <>
+ " + Around the World\n"<>
+ "- Human After All\n" <>
+ " + Technologic\n" <>
" + Robot Rock\n") =?>
bulletList [ mconcat
[ plain "Discovery"
@@ -250,7 +252,7 @@ tests =
]
, "Simple Ordered List" =:
- ("+ Item1\n" ++
+ ("+ Item1\n" <>
"+ Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
@@ -260,7 +262,7 @@ tests =
, "Indented Ordered List" =:
- (" + Item1\n" ++
+ (" + Item1\n" <>
" + Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
@@ -269,11 +271,11 @@ tests =
in orderedListWith listStyle listStructure
, "Nested Ordered Lists" =:
- ("+ One\n" ++
- " + One-One\n" ++
- " + One-Two\n" ++
- "+ Two\n" ++
- " + Two-One\n"++
+ ("+ One\n" <>
+ " + One-One\n" <>
+ " + One-Two\n" <>
+ "+ Two\n" <>
+ " + Two-One\n"<>
" + Two-Two\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ mconcat
@@ -292,19 +294,19 @@ tests =
in orderedListWith listStyle listStructure
, "Ordered List in Bullet List" =:
- ("- Emacs\n" ++
+ ("- Emacs\n" <>
" + Org\n") =?>
bulletList [ (plain "Emacs") <>
(orderedList [ plain "Org"])
]
, "Bullet List in Ordered List" =:
- ("+ GNU\n" ++
+ ("+ GNU\n" <>
" - Freedom\n") =?>
orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ]
, "Definition List" =:
- unlines [ ": PLL"
+ T.unlines [ ": PLL"
, " phase-locked loop"
, ": TTL"
, " transistor-transistor logic"
@@ -318,7 +320,7 @@ tests =
, "Loose bullet list" =:
- unlines [ "- apple"
+ T.unlines [ "- apple"
, ""
, "- orange"
, ""
@@ -340,7 +342,7 @@ tests =
simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ]
, "Multi line table" =:
- unlines [ "| One |"
+ T.unlines [ "| One |"
, "| Two |"
, "| Three |"
] =?>
@@ -355,7 +357,7 @@ tests =
simpleTable' 1 mempty [[mempty]]
, "Glider Table" =:
- unlines [ "| 1 | 0 | 0 |"
+ T.unlines [ "| 1 | 0 | 0 |"
, "| 0 | 1 | 1 |"
, "| 1 | 1 | 0 |"
] =?>
@@ -367,7 +369,7 @@ tests =
, "Table with Header" =:
- unlines [ "|| Species | Status |"
+ T.unlines [ "|| Species | Status |"
, "| cervisiae | domesticated |"
, "| paradoxus | wild |"
] =?>
@@ -377,7 +379,7 @@ tests =
]
, "Table alignment determined by spacing" =:
- unlines [ "| Numbers | Text | More |"
+ T.unlines [ "| Numbers | Text | More |"
, "| 1 | One | foo |"
, "| 2 | Two | bar |"
] =?>
@@ -394,7 +396,7 @@ tests =
, "Table with differing row lengths" =:
- unlines [ "|| Numbers | Text "
+ T.unlines [ "|| Numbers | Text "
, "| 1 | One | foo |"
, "| 2 "
] =?>
@@ -408,23 +410,23 @@ tests =
, testGroup "Blocks and fragments"
[ "Source block" =:
- unlines [ "```"
+ T.unlines [ "```"
, "main = putStrLn greeting"
, " where greeting = \"moin\""
, "```" ] =?>
- let code' = "main = putStrLn greeting\n" ++
+ let code' = "main = putStrLn greeting\n" <>
" where greeting = \"moin\"\n"
in codeBlock code'
, "tagged block" =:
- unlines [ "'''"
+ T.unlines [ "'''"
, "<aside>HTML5 is pretty nice.</aside>"
, "'''"
] =?>
rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n"
, "Quote block" =:
- unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!"
+ T.unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!"
] =?>
blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht,"
, "eine", "Mauer", "zu", "errichten!"
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index 02ecb08f4..6b97c0761 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -1,5 +1,6 @@
module Tests.Writers.AsciiDoc (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -7,7 +8,7 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
asciidoc :: (ToPandoc a) => a -> String
-asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
+asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
tests :: [TestTree]
tests = [ testGroup "emphasis"
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index a5185e19f..783b601a9 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
@@ -9,10 +10,10 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
context :: (ToPandoc a) => a -> String
-context = purely (writeConTeXt def) . toPandoc
+context = unpack . purely (writeConTeXt def) . toPandoc
context' :: (ToPandoc a) => a -> String
-context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc
+context' = unpack . purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs
index d7da51aed..90ae073fa 100644
--- a/test/Tests/Writers/Docbook.hs
+++ b/test/Tests/Writers/Docbook.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Docbook (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -11,7 +12,7 @@ docbook :: (ToPandoc a) => a -> String
docbook = docbookWithOpts def{ writerWrapText = WrapNone }
docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
-docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc
+docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index 2d7179199..215952893 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -10,6 +10,8 @@ import Text.Pandoc.Readers.Docx
import Text.Pandoc.Readers.Native
import Text.Pandoc.Writers.Docx
import System.IO.Unsafe (unsafePerformIO) -- TODO temporary
+import qualified Data.ByteString as BS
+import qualified Text.Pandoc.UTF8 as UTF8
type Options = (WriterOptions, ReaderOptions)
@@ -18,8 +20,8 @@ compareOutput :: Options
-> FilePath
-> IO (Pandoc, Pandoc)
compareOutput opts nativeFileIn nativeFileOut = do
- nf <- Prelude.readFile nativeFileIn
- nf' <- Prelude.readFile nativeFileOut
+ nf <- UTF8.toText <$> BS.readFile nativeFileIn
+ nf' <- UTF8.toText <$> BS.readFile nativeFileOut
let wopts = fst opts
df <- runIOorExplode $ do
d <- readNative def nf
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
index 4246b033d..23ff718d3 100644
--- a/test/Tests/Writers/HTML.hs
+++ b/test/Tests/Writers/HTML.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -8,7 +9,7 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
html :: (ToPandoc a) => a -> String
-html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
+html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs
index 5f8aea3e0..471d9d9e7 100644
--- a/test/Tests/Writers/LaTeX.hs
+++ b/test/Tests/Writers/LaTeX.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -14,10 +15,10 @@ latexListing :: (ToPandoc a) => a -> String
latexListing = latexWithOpts def{ writerListings = True }
latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-latexWithOpts opts = purely (writeLaTeX opts) . toPandoc
+latexWithOpts opts = unpack . purely (writeLaTeX opts) . toPandoc
beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-beamerWithOpts opts = purely (writeBeamer opts) . toPandoc
+beamerWithOpts opts = unpack . purely (writeBeamer opts) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs
index 5b1e76a29..012e0888c 100644
--- a/test/Tests/Writers/Markdown.hs
+++ b/test/Tests/Writers/Markdown.hs
@@ -2,6 +2,7 @@
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Tests.Writers.Markdown (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -12,10 +13,10 @@ defopts :: WriterOptions
defopts = def{ writerExtensions = pandocExtensions }
markdown :: (ToPandoc a) => a -> String
-markdown = purely (writeMarkdown defopts) . toPandoc
+markdown = unpack . purely (writeMarkdown defopts) . toPandoc
markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x
+markdownWithOpts opts x = unpack . purely (writeMarkdown opts) $ toPandoc x
{-
"my test" =: X =?> Y
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index 9a7dec580..63fdd293c 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -1,5 +1,6 @@
module Tests.Writers.Muse (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -10,7 +11,7 @@ muse :: (ToPandoc a) => a -> String
muse = museWithOpts def{ writerWrapText = WrapNone }
museWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-museWithOpts opts = purely (writeMuse opts) . toPandoc
+museWithOpts opts = unpack . purely (writeMuse opts) . toPandoc
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
@@ -155,8 +156,8 @@ tests = [ testGroup "block elements"
,[para $ text "Para 2.1", para $ text "Para 2.2"]]
in simpleTable [] rows
=?>
- unlines [ "Para 1.1 | Para 1.2"
- , "Para 2.1 | Para 2.2"
+ unlines [ " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
]
, "table with header" =:
let headers = [plain $ text "header 1", plain $ text "header 2"]
@@ -164,9 +165,9 @@ tests = [ testGroup "block elements"
,[para $ text "Para 2.1", para $ text "Para 2.2"]]
in simpleTable headers rows
=?>
- unlines [ "header 1 || header 2"
- , "Para 1.1 | Para 1.2"
- , "Para 2.1 | Para 2.2"
+ unlines [ " header 1 || header 2"
+ , " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
]
, "table with header and caption" =:
let caption = text "Table 1"
@@ -174,10 +175,10 @@ tests = [ testGroup "block elements"
rows = [[para $ text "Para 1.1", para $ text "Para 1.2"]
,[para $ text "Para 2.1", para $ text "Para 2.2"]]
in table caption mempty headers rows
- =?> unlines [ "header 1 || header 2"
- , "Para 1.1 | Para 1.2"
- , "Para 2.1 | Para 2.2"
- , "|+ Table 1 +|"
+ =?> unlines [ " header 1 || header 2"
+ , " Para 1.1 | Para 1.2"
+ , " Para 2.1 | Para 2.2"
+ , " |+ Table 1 +|"
]
]
-- Div is trivial
diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs
index c92cb905c..c22185968 100644
--- a/test/Tests/Writers/Native.hs
+++ b/test/Tests/Writers/Native.hs
@@ -1,5 +1,6 @@
module Tests.Writers.Native (tests) where
+import Data.Text (unpack)
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
@@ -8,12 +9,11 @@ import Text.Pandoc.Arbitrary ()
p_write_rt :: Pandoc -> Bool
p_write_rt d =
- read (purely (writeNative def{ writerTemplate = Just "" }) d) == d
+ read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d
p_write_blocks_rt :: [Block] -> Bool
p_write_blocks_rt bs =
- read (purely (writeNative def) (Pandoc nullMeta bs)) ==
- bs
+ read (unpack $ purely (writeNative def) (Pandoc nullMeta bs)) == bs
tests :: [TestTree]
tests = [ testProperty "p_write_rt" p_write_rt
diff --git a/test/command/1718.md b/test/command/1718.md
new file mode 100644
index 000000000..401610a7a
--- /dev/null
+++ b/test/command/1718.md
@@ -0,0 +1,11 @@
+```
+% pandoc -t native
+Note[^1].
+
+[^1]: the first note.
+
+[^2]: the second, unused, note.
+^D
+[warning] Note with key '2' defined at line 5 column 1 but not used.
+[Para [Str "Note",Note [Para [Str "the",Space,Str "first",Space,Str "note."]],Str "."]]
+```
diff --git a/test/command/1841.md b/test/command/1841.md
new file mode 100644
index 000000000..408f224bd
--- /dev/null
+++ b/test/command/1841.md
@@ -0,0 +1,42 @@
+```
+% pandoc
+<table>
+<tr>
+<td> *one*</td>
+<td> [a link](http://google.com)</td>
+</tr>
+</table>
+^D
+<table>
+<tr>
+<td>
+<em>one</em>
+</td>
+<td>
+<a href="http://google.com">a link</a>
+</td>
+</tr>
+</table>
+```
+
+```
+% pandoc
+<table>
+ <tr>
+ <td>*one*</td>
+ <td>[a link](http://google.com)</td>
+ </tr>
+</table>
+^D
+<table>
+<tr>
+<td>
+<em>one</em>
+</td>
+<td>
+<a href="http://google.com">a link</a>
+</td>
+</tr>
+</table>
+```
+
diff --git a/test/command/2228.md b/test/command/2228.md
new file mode 100644
index 000000000..589a2350e
--- /dev/null
+++ b/test/command/2228.md
@@ -0,0 +1,6 @@
+```
+% pandoc -f markdown+smart -t latex+smart
+*foo*'s 'foo'
+^D
+\emph{foo}'s `foo'
+```
diff --git a/test/command/2602.md b/test/command/2602.md
new file mode 100644
index 000000000..5ed4b581c
--- /dev/null
+++ b/test/command/2602.md
@@ -0,0 +1,18 @@
+```
+% pandoc
+[a] [b]
+
+[b]: url
+^D
+<p>[a] <a href="url">b</a></p>
+```
+
+```
+% pandoc -f markdown+spaced_reference_links
+[a] [b]
+
+[b]: url
+^D
+<p><a href="url">a</a></p>
+```
+
diff --git a/test/command/3113.md b/test/command/3113.md
new file mode 100644
index 000000000..f44e25709
--- /dev/null
+++ b/test/command/3113.md
@@ -0,0 +1,13 @@
+```
+% pandoc -f latex -t native
+\begin{eqnarray}
+A&=&B,\\
+C&=&D,\\
+%\end{eqnarray}
+%\begin{eqnarray}
+E&=&F
+\end{eqnarray}
+^D
+[Para [Math DisplayMath "\\begin{aligned}\nA&=&B,\\\\\nC&=&D,\\\\\nE&=&F\\end{aligned}"]]
+```
+
diff --git a/test/command/3314.md b/test/command/3314.md
new file mode 100644
index 000000000..064b04cbd
--- /dev/null
+++ b/test/command/3314.md
@@ -0,0 +1,34 @@
+See #3315 and <http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#simple-tables>.
+
+```
+% pandoc -f org -t html5
++-----------+-------+----------+
+| First | 12.0 | Example |
+| | | row |
+| | | spanning |
+| | | lines |
++-----------+-------+----------+
+| Second | 5.0 | Another |
++-----------+-------+----------+
+^D
+<table style="width:43%;">
+<colgroup>
+<col style="width: 16%" />
+<col style="width: 11%" />
+<col style="width: 15%" />
+</colgroup>
+<tbody>
+<tr class="odd">
+<td>First</td>
+<td>12.0</td>
+<td>Example row spanning lines</td>
+</tr>
+<tr class="even">
+<td>Second</td>
+<td>5.0</td>
+<td>Another</td>
+</tr>
+</tbody>
+</table>
+```
+
diff --git a/test/command/3401.md b/test/command/3401.md
new file mode 100644
index 000000000..99528553a
--- /dev/null
+++ b/test/command/3401.md
@@ -0,0 +1,19 @@
+See #3401 and <http://orgmode.org/manual/Macro-replacement.html>
+
+```
+% pandoc -f org -t native
+#+MACRO: HELLO /Hello, $1/
+{{{HELLO(World)}}}
+^D
+[Para [Emph [Str "Hello,",Space,Str "World"]]]
+```
+
+Inverted argument order
+
+```
+% pandoc -f org -t native
+#+MACRO: A $2,$1
+{{{A(1,2)}}}
+^D
+[Para [Str "2,1"]]
+```
diff --git a/test/command/3432.md b/test/command/3432.md
new file mode 100644
index 000000000..7264d22c3
--- /dev/null
+++ b/test/command/3432.md
@@ -0,0 +1,289 @@
+List-table with header-rows and widths options.
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+ :widths: 15 10 30
+ :header-rows: 1
+
+ * - Treat
+ - Quantity
+ - Description
+ * - Albatross
+ - 2.99
+ - On a stick!
+ * - Crunchy Frog
+ - 1.49
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<colgroup>
+<col style="width: 27%" />
+<col style="width: 18%" />
+<col style="width: 54%" />
+</colgroup>
+<thead>
+<tr class="header">
+<th>Treat</th>
+<th>Quantity</th>
+<th>Description</th>
+</tr>
+</thead>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td>On a stick!</td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td>1.49</td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
+
+List-table whose widths is "auto".
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+ :header-rows: 1
+ :widths: auto
+
+ * - Treat
+ - Quantity
+ - Description
+ * - Albatross
+ - 2.99
+ - On a stick!
+ * - Crunchy Frog
+ - 1.49
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<thead>
+<tr class="header">
+<th>Treat</th>
+<th>Quantity</th>
+<th>Description</th>
+</tr>
+</thead>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td>On a stick!</td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td>1.49</td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
+
+
+List-table with header-rows which is bigger than 1. Only the first row is treated as a header.
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+ :header-rows: 2
+
+ * - Treat
+ - Quantity
+ - Description
+ * - Albatross
+ - 2.99
+ - On a stick!
+ * - Crunchy Frog
+ - 1.49
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<thead>
+<tr class="header">
+<th>Treat</th>
+<th>Quantity</th>
+<th>Description</th>
+</tr>
+</thead>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td>On a stick!</td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td>1.49</td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
+
+List-table without header-rows.
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+
+ * - Albatross
+ - 2.99
+ - On a stick!
+ * - Crunchy Frog
+ - 1.49
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td>On a stick!</td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td>1.49</td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
+
+List-table with empty cells. You need a space after '-', otherwise the row will disapear. Parser for Bulletlists causes this ristriction.
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+ :header-rows: 2
+
+ * - Treat
+ - Quantity
+ - Description
+ * - Albatross
+ - 2.99
+ -
+ * - Crunchy Frog
+ -
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<thead>
+<tr class="header">
+<th>Treat</th>
+<th>Quantity</th>
+<th>Description</th>
+</tr>
+</thead>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td></td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td></td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
+
+List-table with a cell having a bulletlist
+
+```
+% pandoc -f rst
+.. list-table:: Frozen Delights!
+
+ * - Albatross
+ - 2.99
+ - + On a stick!
+ + In a cup!
+ * - Crunchy Frog
+ - 1.49
+ - If we took the bones out, it wouldn't be
+ crunchy, now would it?
+ * - Gannet Ripple
+ - 1.99
+ - On a stick!
+^D
+<table>
+<caption>Frozen Delights!</caption>
+<tbody>
+<tr class="odd">
+<td>Albatross</td>
+<td>2.99</td>
+<td><ul>
+<li>On a stick!</li>
+<li>In a cup!</li>
+</ul></td>
+</tr>
+<tr class="even">
+<td>Crunchy Frog</td>
+<td>1.49</td>
+<td>If we took the bones out, it wouldn't be crunchy, now would it?</td>
+</tr>
+<tr class="odd">
+<td>Gannet Ripple</td>
+<td>1.99</td>
+<td>On a stick!</td>
+</tr>
+</tbody>
+</table>
+```
diff --git a/test/command/3450.md b/test/command/3450.md
new file mode 100644
index 000000000..8759aa0c1
--- /dev/null
+++ b/test/command/3450.md
@@ -0,0 +1,12 @@
+```
+% pandoc -fmarkdown-implicit_figures
+![image](lalune.jpg){height=2em}
+^D
+<p><img src="lalune.jpg" alt="image" style="height:2em" /></p>
+```
+```
+% pandoc -fmarkdown-implicit_figures -t latex
+![image](lalune.jpg){height=2em}
+^D
+\includegraphics[height=2em]{lalune.jpg}
+```
diff --git a/test/command/3494.md b/test/command/3494.md
index faa58c321..7c480fde6 100644
--- a/test/command/3494.md
+++ b/test/command/3494.md
@@ -1,5 +1,5 @@
```
-% pandoc -f latex
+% pandoc -f latex --quiet
\begin{table}[h!]
\begin{tabular}{r|l|l}
diff --git a/test/command/3510-export.latex b/test/command/3510-export.latex
new file mode 100644
index 000000000..6d8636322
--- /dev/null
+++ b/test/command/3510-export.latex
@@ -0,0 +1 @@
+\emph{Hello} \ No newline at end of file
diff --git a/test/command/3510-src.hs b/test/command/3510-src.hs
new file mode 100644
index 000000000..ad5744b80
--- /dev/null
+++ b/test/command/3510-src.hs
@@ -0,0 +1 @@
+putStrLn outString
diff --git a/test/command/3510-subdoc.org b/test/command/3510-subdoc.org
new file mode 100644
index 000000000..5bcc6678a
--- /dev/null
+++ b/test/command/3510-subdoc.org
@@ -0,0 +1,5 @@
+* Subsection
+
+Included text
+
+Lorem ipsum.
diff --git a/test/command/3510.md b/test/command/3510.md
new file mode 100644
index 000000000..7993db848
--- /dev/null
+++ b/test/command/3510.md
@@ -0,0 +1,20 @@
+See <http://orgmode.org/manual/Include-files.html>
+```
+% pandoc -f org -t native
+Text
+
+#+include: "command/3510-subdoc.org"
+
+#+INCLUDE: "command/3510-src.hs" src haskell
+#+INCLUDE: "command/3510-export.latex" export latex
+
+More text
+^D
+[Para [Str "Text"]
+,Header 1 ("subsection",[],[]) [Str "Subsection"]
+,Para [Str "Included",Space,Str "text"]
+,Plain [Str "Lorem",Space,Str "ipsum."]
+,CodeBlock ("",["haskell"],[]) "putStrLn outString\n"
+,RawBlock (Format "latex") "\\emph{Hello}"
+,Para [Str "More",Space,Str "text"]]
+```
diff --git a/test/command/3516.md b/test/command/3516.md
index 982043874..8c7e478d3 100644
--- a/test/command/3516.md
+++ b/test/command/3516.md
@@ -27,8 +27,8 @@ on Windows builds.
[Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
[[]
,[]]
- [[[Para [Str "1"]]
- ,[Para [Str "2"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "2"]]]
,[[]
,[]]]]
```
diff --git a/test/command/3577.md b/test/command/3577.md
index bfeb86eaa..dc88937e9 100644
--- a/test/command/3577.md
+++ b/test/command/3577.md
@@ -1,5 +1,5 @@
```
-% pandoc -f latex -t html5
+% pandoc -f latex -t html5 --quiet
\begin{figure}[ht]
\begin{subfigure}{0.45\textwidth}
\centering
diff --git a/test/command/3585.md b/test/command/3585.md
new file mode 100644
index 000000000..739ddeea4
--- /dev/null
+++ b/test/command/3585.md
@@ -0,0 +1,16 @@
+```
+% pandoc -f mediawiki+smart -t native
+"Hello"
+
+Same but bzip2 it and nice it <tt>zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org "> /storage/c-3po/tank-storage-data-svn.dmp.bz2"</tt>
+^D
+[Para [Quoted DoubleQuote [Str "Hello"]]
+,Para [Str "Same",Space,Str "but",Space,Str "bzip2",Space,Str "it",Space,Str "and",Space,Str "nice",Space,Str "it",Space,Code ("",[],[]) "zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org \"> /storage/c-3po/tank-storage-data-svn.dmp.bz2\""]]
+```
+
+```
+% pandoc -f mediawiki -t native
+"Hello"
+^D
+[Para [Str "\"Hello\""]]
+```
diff --git a/test/command/3619.md b/test/command/3619.md
new file mode 100644
index 000000000..62962c43b
--- /dev/null
+++ b/test/command/3619.md
@@ -0,0 +1,28 @@
+```
+% pandoc -f html -t markdown --reference-links
+<a href="foo">bar</a>: baz
+^D
+[bar][]: baz
+
+ [bar]: foo
+```
+
+```
+% pandoc -f html -t markdown --reference-links
+<a href="foo">bar</a>(baz)
+^D
+[bar][](baz)
+
+ [bar]: foo
+```
+
+```
+% pandoc -f html -t markdown_strict --reference-links
+<a href="a">foo</a><br/><a href="b">bar</a>
+^D
+[foo][]
+[bar]
+
+ [foo]: a
+ [bar]: b
+```
diff --git a/test/command/3630.md b/test/command/3630.md
new file mode 100644
index 000000000..db3a17dda
--- /dev/null
+++ b/test/command/3630.md
@@ -0,0 +1,8 @@
+```
+% pandoc -f markdown -t markdown --reference-links
+![foo](bar.png){#myId}
+^D
+![foo]
+
+ [foo]: bar.png {#myId}
+```
diff --git a/test/command/3667.md b/test/command/3667.md
new file mode 100644
index 000000000..97de8f598
--- /dev/null
+++ b/test/command/3667.md
@@ -0,0 +1,13 @@
+```
+% pandoc -f textile
+| "link text":http://example.com/ |
+^D
+<table>
+<tbody>
+<tr class="odd">
+<td><a href="http://example.com/">link text</a></td>
+</tr>
+</tbody>
+</table>
+```
+
diff --git a/test/command/3674.md b/test/command/3674.md
new file mode 100644
index 000000000..92ed4bed7
--- /dev/null
+++ b/test/command/3674.md
@@ -0,0 +1,39 @@
+Make sure we don't get duplicate reference links, even with
+`--reference-location=section`.
+
+```
+% pandoc --reference-links -t markdown --reference-location=section --atx-headers
+# a
+
+![](a)
+
+# b
+
+![](b)
+
+^D
+# a
+
+![][1]
+
+ [1]: a
+
+# b
+
+![][2]
+
+ [2]: b
+```
+
+Subsidiary issue: allow line break between reference link
+url/title and attributes:
+
+```
+% pandoc
+[a]
+
+[a]: url
+{.class}
+^D
+<p><a href="url" class="class">a</a></p>
+```
diff --git a/test/command/3675.md b/test/command/3675.md
new file mode 100644
index 000000000..b129c7a63
--- /dev/null
+++ b/test/command/3675.md
@@ -0,0 +1,15 @@
+````
+% pandoc -t rst
+```python
+print("hello")
+```
+> block quote
+^D
+.. code:: python
+
+ print("hello")
+
+..
+
+ block quote
+````
diff --git a/test/command/3690.md b/test/command/3690.md
new file mode 100644
index 000000000..213b88138
--- /dev/null
+++ b/test/command/3690.md
@@ -0,0 +1,8 @@
+```
+% pandoc
+- [o] _hi_
+^D
+<ul>
+<li>[o] <em>hi</em></li>
+</ul>
+```
diff --git a/test/command/3701.md b/test/command/3701.md
new file mode 100644
index 000000000..01e438639
--- /dev/null
+++ b/test/command/3701.md
@@ -0,0 +1,60 @@
+```
+% pandoc --reference-location=block -t markdown --reference-links --wrap=preserve
+[a](u)
+
+[a](u)
+
+[a](u2)
+[A](u)
+[a](u){.foo}
+
+[a](u3)
+^D
+[a]
+
+ [a]: u
+
+[a]
+
+ [a]: u
+
+[a][1]
+[A][]
+[a][2]
+
+ [1]: u2
+ [A]: u
+ [2]: u {.foo}
+
+[a][3]
+
+ [3]: u3
+```
+
+```
+% pandoc
+[a]
+
+ [a]: u
+
+[a]
+
+ [a]: u
+
+[a][1]
+[A][]
+[a][2]
+
+ [1]: u2
+ [A]: u
+ [2]: u {.foo}
+
+[a][3]
+
+ [3]: u3
+^D
+<p><a href="u">a</a></p>
+<p><a href="u">a</a></p>
+<p><a href="u2">a</a> <a href="u">A</a> <a href="u" class="foo">a</a></p>
+<p><a href="u3">a</a></p>
+```
diff --git a/test/command/3706.md b/test/command/3706.md
new file mode 100644
index 000000000..00f53279e
--- /dev/null
+++ b/test/command/3706.md
@@ -0,0 +1,44 @@
+Results marker can be hidden in block attributes (#3706)
+
+```
+pandoc -f org -t native
+#+BEGIN_SRC R :exports results :colnames yes
+ data.frame(Id = 1:3, Desc = rep("La",3))
+#+END_SRC
+
+#+CAPTION: Lalelu.
+#+LABEL: tab
+#+RESULTS:
+| Id | Desc |
+|----+------|
+| 1 | La |
+| 2 | La |
+| 3 | La |
+^D
+[Table [Str "Lalelu."] [AlignDefault,AlignDefault] [0.0,0.0]
+ [[Plain [Str "Id"]]
+ ,[Plain [Str "Desc"]]]
+ [[[Plain [Str "1"]]
+ ,[Plain [Str "La"]]]
+ ,[[Plain [Str "2"]]
+ ,[Plain [Str "La"]]]
+ ,[[Plain [Str "3"]]
+ ,[Plain [Str "La"]]]]]
+```
+
+```
+pandoc -f org -t native
+#+BEGIN_SRC R :exports none :colnames yes
+ data.frame(Id = 1:2, Desc = rep("La",2))
+#+END_SRC
+
+#+CAPTION: Lalelu.
+#+LABEL: tab
+#+RESULTS:
+| Id | Desc |
+|----+------|
+| 1 | La |
+| 2 | La |
+^D
+[]
+```
diff --git a/test/command/3708.md b/test/command/3708.md
new file mode 100644
index 000000000..2cbc82c25
--- /dev/null
+++ b/test/command/3708.md
@@ -0,0 +1,15 @@
+```
+% pandoc -f latex -t native
+\begin{tabular}{cc}
+ A & B\&1 \\
+ C & D
+\end{tabular}
+^D
+[Table [] [AlignCenter,AlignCenter] [0.0,0.0]
+ [[]
+ ,[]]
+ [[[Plain [Str "A"]]
+ ,[Plain [Str "B&1"]]]
+ ,[[Plain [Str "C"]]
+ ,[Plain [Str "D"]]]]]
+```
diff --git a/test/command/3715.md b/test/command/3715.md
new file mode 100644
index 000000000..9d74779cb
--- /dev/null
+++ b/test/command/3715.md
@@ -0,0 +1,15 @@
+```
+% pandoc -t markdown -f html --wrap=preserve
+x<em></em>x
+y<strong></strong>y
+z<sup></sup>z
+w<sub></sub>w
+q<s></s>q
+^D
+xx
+yy
+zz
+ww
+qq
+```
+
diff --git a/test/command/3716.md b/test/command/3716.md
new file mode 100644
index 000000000..7e00819da
--- /dev/null
+++ b/test/command/3716.md
@@ -0,0 +1,6 @@
+```
+% pandoc
+<http://example.com>{.foo}
+^D
+<p><a href="http://example.com" class="uri foo">http://example.com</a></p>
+```
diff --git a/test/command/3730.md b/test/command/3730.md
new file mode 100644
index 000000000..fbc06cbce
--- /dev/null
+++ b/test/command/3730.md
@@ -0,0 +1,21 @@
+````
+% pandoc
+nice line\
+```
+code
+```
+^D
+<p>nice line<br />
+</p>
+<pre><code>code</code></pre>
+````
+
+```
+% pandoc
+# hi\
+there
+^D
+<h1 id="hi">hi<br />
+</h1>
+<p>there</p>
+```
diff --git a/test/command/3736.md b/test/command/3736.md
new file mode 100644
index 000000000..b66e0a359
--- /dev/null
+++ b/test/command/3736.md
@@ -0,0 +1,25 @@
+```
+% pandoc --wrap=preserve -f html -t markdown
+<h2>hi
+there</h2>
+^D
+hi there
+--------
+```
+
+```
+% pandoc --wrap=preserve -f html -t markdown
+<h2>hi <em>there
+again</em></h2>
+^D
+hi *there again*
+----------------
+```
+
+```
+% pandoc --wrap=preserve -f html -t markdown
+<h2>hi<br>there</h2>
+^D
+hi there
+--------
+```
diff --git a/test/command/512.md b/test/command/512.md
index a13c434f6..52e5dbe07 100644
--- a/test/command/512.md
+++ b/test/command/512.md
@@ -36,6 +36,7 @@ Loop detection:
__ link1_
^D
+[warning] Circular reference 'link1' at line 1 column 15
<p><a href="">click here</a></p>
```
diff --git a/test/command/SVG_logo-without-xml-declaration.svg b/test/command/SVG_logo-without-xml-declaration.svg
new file mode 100644
index 000000000..febcab6ca
--- /dev/null
+++ b/test/command/SVG_logo-without-xml-declaration.svg
@@ -0,0 +1,32 @@
+<svg viewBox="-50 -50 100 100" xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink">
+<title>SVG Logo</title>
+<rect id="background" x="-50" y="-50" width="100" height="100" rx="4" fill="#f90"/>
+<rect id="top-left" x="-50" y="-50" width="50" height="50" rx="4" fill="#ffb13b"/>
+<rect id="bottom-right" width="50" height="50" rx="4" fill="#de8500"/>
+<use stroke="#f90" stroke-width="22.6" xlink:href="#a"/>
+<circle r="26"/>
+<use stroke="#000" stroke-width="12" xlink:href="#a"/>
+<g id="a">
+ <g id="b">
+ <g id="c">
+ <circle id="n" cy="-31.6" r="7.1" fill="#fff"/>
+ <path d="m0 31.6v-63.2" stroke="#fff" stroke-width="10"/>
+ <use y="63.2" xlink:href="#n"/>
+ </g>
+ <use transform="rotate(90)" xlink:href="#c"/>
+ </g>
+ <use transform="rotate(45)" xlink:href="#b"/>
+</g>
+<path id="text-backdrop" d="m44.68 0v40c0 3.333-1.667 5-5 5h-79.38c-3.333 0-5-1.667-5-5v-40"/>
+<path id="shine" d="m36 4.21c2.9 0 5.3 2.4 5.3 5.3v18c-27.6-3.4-54.9-8-82-7.7v-10.2c0-2.93 2.4-5.3 5.3-5.3z" fill="#3f3f3f"/>
+<use stroke="#000" stroke-width="7.4" xlink:href="#s"/>
+<g id="svg-text" stroke="#fff" stroke-width="6.4">
+ <g id="s">
+ <path fill="none" d="m-31.74 31.17a8.26 8.26 0 1 0 8.26 -8.26 8.26 8.26 0 1 1 8.26 -8.26M23.23 23h8.288v 8.26a8.26 8.26 0 0 1 -16.52 0v-16.52a8.26 8.26 0 0 1 16.52 0"/>
+ <g stroke-width=".5" stroke="#000">
+ <path d="m4.76 3h6.83l-8.24 39.8h-6.85l-8.26-39.8h6.85l4.84 23.3z" fill="#fff"/>
+ <path d="m23.23 19.55v6.9m4.838-11.71h6.9m-70.16 16.43h6.9m9.62-16.52h6.9" stroke-linecap="square"/>
+ </g>
+ </g>
+</g>
+</svg>
diff --git a/test/command/SVG_logo.svg b/test/command/SVG_logo.svg
new file mode 100644
index 000000000..5333a5ddb
--- /dev/null
+++ b/test/command/SVG_logo.svg
@@ -0,0 +1,33 @@
+<?xml version="1.0"?>
+<svg viewBox="-50 -50 100 100" xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink">
+<title>SVG Logo</title>
+<rect id="background" x="-50" y="-50" width="100" height="100" rx="4" fill="#f90"/>
+<rect id="top-left" x="-50" y="-50" width="50" height="50" rx="4" fill="#ffb13b"/>
+<rect id="bottom-right" width="50" height="50" rx="4" fill="#de8500"/>
+<use stroke="#f90" stroke-width="22.6" xlink:href="#a"/>
+<circle r="26"/>
+<use stroke="#000" stroke-width="12" xlink:href="#a"/>
+<g id="a">
+ <g id="b">
+ <g id="c">
+ <circle id="n" cy="-31.6" r="7.1" fill="#fff"/>
+ <path d="m0 31.6v-63.2" stroke="#fff" stroke-width="10"/>
+ <use y="63.2" xlink:href="#n"/>
+ </g>
+ <use transform="rotate(90)" xlink:href="#c"/>
+ </g>
+ <use transform="rotate(45)" xlink:href="#b"/>
+</g>
+<path id="text-backdrop" d="m44.68 0v40c0 3.333-1.667 5-5 5h-79.38c-3.333 0-5-1.667-5-5v-40"/>
+<path id="shine" d="m36 4.21c2.9 0 5.3 2.4 5.3 5.3v18c-27.6-3.4-54.9-8-82-7.7v-10.2c0-2.93 2.4-5.3 5.3-5.3z" fill="#3f3f3f"/>
+<use stroke="#000" stroke-width="7.4" xlink:href="#s"/>
+<g id="svg-text" stroke="#fff" stroke-width="6.4">
+ <g id="s">
+ <path fill="none" d="m-31.74 31.17a8.26 8.26 0 1 0 8.26 -8.26 8.26 8.26 0 1 1 8.26 -8.26M23.23 23h8.288v 8.26a8.26 8.26 0 0 1 -16.52 0v-16.52a8.26 8.26 0 0 1 16.52 0"/>
+ <g stroke-width=".5" stroke="#000">
+ <path d="m4.76 3h6.83l-8.24 39.8h-6.85l-8.26-39.8h6.85l4.84 23.3z" fill="#fff"/>
+ <path d="m23.23 19.55v6.9m4.838-11.71h6.9m-70.16 16.43h6.9m9.62-16.52h6.9" stroke-linecap="square"/>
+ </g>
+ </g>
+</g>
+</svg>
diff --git a/test/command/corrupt.svg b/test/command/corrupt.svg
new file mode 100644
index 000000000..cfaa697f0
--- /dev/null
+++ b/test/command/corrupt.svg
@@ -0,0 +1,5 @@
+Lorem ipsum dolor sit amet etiam. A pede dolor neque pretium luctus pharetra vel rutrum. Orci nonummy ac. At eu est tempor
+proin wisi. Nunc tincidunt proin. Suspendisse lorem commodo. Integer diam diam semper commodo dictum et tellus eu ultrices
+nec erat pulvinar porttitor nulla nulla mauris orci libero eros elementum et possimus voluptate. Velit morbi et. Luctus diam
+in. Lorem tincidunt sem dolor rerum mauris. Dis taciti posuere pellentesque sed rutrum. Lectus donec fusce in dictum pede.
+In etiam congue. Aliquam aliquet elit arcu mauris enim. Risus at enim.
diff --git a/test/command/inkscape-cube.svg b/test/command/inkscape-cube.svg
new file mode 100644
index 000000000..995c3c734
--- /dev/null
+++ b/test/command/inkscape-cube.svg
@@ -0,0 +1,119 @@
+<?xml version="1.0" encoding="UTF-8" standalone="no"?>
+<!-- Created with Inkscape (http://www.inkscape.org/) -->
+
+<svg
+ xmlns:dc="http://purl.org/dc/elements/1.1/"
+ xmlns:cc="http://creativecommons.org/ns#"
+ xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
+ xmlns:svg="http://www.w3.org/2000/svg"
+ xmlns="http://www.w3.org/2000/svg"
+ xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
+ xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
+ width="38.772217mm"
+ height="46.163891mm"
+ viewBox="0 0 38.772217 46.163891"
+ version="1.1"
+ id="svg8"
+ inkscape:version="0.92.1 r"
+ sodipodi:docname="cube.svg">
+ <defs
+ id="defs2">
+ <inkscape:perspective
+ sodipodi:type="inkscape:persp3d"
+ inkscape:vp_x="-48.380952 : -45.023815 : 1"
+ inkscape:vp_y="0 : 1000 : 0"
+ inkscape:vp_z="161.61905 : -45.023817 : 1"
+ inkscape:persp3d-origin="56.619048 : -94.523816 : 1"
+ id="perspective4485" />
+ </defs>
+ <sodipodi:namedview
+ id="base"
+ pagecolor="#ffffff"
+ bordercolor="#666666"
+ borderopacity="1.0"
+ inkscape:pageopacity="0.0"
+ inkscape:pageshadow="2"
+ inkscape:zoom="0.98994949"
+ inkscape:cx="-63.181251"
+ inkscape:cy="-116.38602"
+ inkscape:document-units="mm"
+ inkscape:current-layer="layer1"
+ showgrid="false"
+ fit-margin-top="0"
+ fit-margin-left="0"
+ fit-margin-right="0"
+ fit-margin-bottom="0"
+ inkscape:window-width="1920"
+ inkscape:window-height="1136"
+ inkscape:window-x="1920"
+ inkscape:window-y="30"
+ inkscape:window-maximized="1" />
+ <metadata
+ id="metadata5">
+ <rdf:RDF>
+ <cc:Work
+ rdf:about="">
+ <dc:format>image/svg+xml</dc:format>
+ <dc:type
+ rdf:resource="http://purl.org/dc/dcmitype/StillImage" />
+ <dc:title></dc:title>
+ </cc:Work>
+ </rdf:RDF>
+ </metadata>
+ <g
+ inkscape:label="Ebene 1"
+ inkscape:groupmode="layer"
+ id="layer1"
+ transform="translate(-149.67857,78.746839)">
+ <g
+ sodipodi:type="inkscape:box3d"
+ id="g4487"
+ style="opacity:0.2;fill:none;fill-opacity:1;stroke:#000000;stroke-width:0.53100002;stroke-linecap:round;stroke-linejoin:miter;stroke-miterlimit:10;stroke-dasharray:none;stroke-dashoffset:0;stroke-opacity:1"
+ inkscape:perspectiveID="#perspective4485"
+ inkscape:corner0="1.1045097 : 0.18860662 : 0 : 1"
+ inkscape:corner7="0.52634769 : 0.15538942 : 0.25 : 1">
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4489"
+ style="fill:#353564;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="6"
+ d="m 151.19047,-53.658435 v 15.783818 l 17.00006,5.342459 v -14.107905 z"
+ points="151.19047,-37.874617 168.19053,-32.532158 168.19053,-46.640063 151.19047,-53.658435 " />
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4499"
+ style="fill:#e9e9ff;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="11"
+ d="m 168.19053,-46.640063 21.77216,-19.229539 v 18.699717 l -21.77216,14.637727 z"
+ points="189.96269,-65.869602 189.96269,-47.169885 168.19053,-32.532158 168.19053,-46.640063 " />
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4491"
+ style="fill:#4d4d9f;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="5"
+ d="m 151.19047,-53.658435 18.89881,-25.037614 19.87341,12.826447 -21.77216,19.229539 z"
+ points="170.08928,-78.696049 189.96269,-65.869602 168.19053,-46.640063 151.19047,-53.658435 " />
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4497"
+ style="fill:#afafde;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="13"
+ d="m 151.19047,-37.874617 18.89881,-19.058894 19.87341,9.763626 -21.77216,14.637727 z"
+ points="170.08928,-56.933511 189.96269,-47.169885 168.19053,-32.532158 151.19047,-37.874617 " />
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4495"
+ style="fill:#d7d7ff;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="14"
+ d="m 170.08928,-78.696049 v 21.762538 l 19.87341,9.763626 v -18.699717 z"
+ points="170.08928,-56.933511 189.96269,-47.169885 189.96269,-65.869602 170.08928,-78.696049 " />
+ <path
+ sodipodi:type="inkscape:box3dside"
+ id="path4493"
+ style="fill:#8686bf;fill-rule:evenodd;stroke:none;stroke-width:1px;stroke-linecap:butt;stroke-linejoin:round;stroke-opacity:1"
+ inkscape:box3dsidetype="3"
+ d="m 151.19047,-53.658435 18.89881,-25.037614 v 21.762538 l -18.89881,19.058894 z"
+ points="170.08928,-78.696049 170.08928,-56.933511 151.19047,-37.874617 151.19047,-53.658435 " />
+ </g>
+ </g>
+</svg>
diff --git a/test/command/latex-fontawesome.md b/test/command/latex-fontawesome.md
new file mode 100644
index 000000000..2a7e91185
--- /dev/null
+++ b/test/command/latex-fontawesome.md
@@ -0,0 +1,13 @@
+```
+% pandoc -f latex -t native
+Check: \faCheck
+^D
+[Para [Str "Check:",Space,Str "\10003"]]
+```
+
+```
+% pandoc -f latex -t native
+Close: \faClose
+^D
+[Para [Str "Close:",Space,Str "\10007"]]
+```
diff --git a/test/command/lstlisting.md b/test/command/lstlisting.md
new file mode 100644
index 000000000..d928cc702
--- /dev/null
+++ b/test/command/lstlisting.md
@@ -0,0 +1,25 @@
+```
+% pandoc -f latex -t native
+\begin{lstlisting}[language=Java, caption={Java Example}, label=lst:Hello-World]
+public class World {
+ public static void main(String[] args) {
+ System.out.println("Hello World");
+ }
+}
+\end{lstlisting}
+^D
+[CodeBlock ("lst:Hello-World",["java"],[("language","Java"),("caption","Java Example"),("label","lst:Hello-World")]) "public class World {\n public static void main(String[] args) {\n System.out.println(\"Hello World\");\n }\n}"]
+```
+
+```
+% pandoc -f latex -t native
+\begin{lstlisting}[language=Java, escapechar=|, caption={Java Example}, label=lst:Hello-World]
+public class World {
+ public static void main(String[] args) {
+ System.out.println("Hello World");
+ }
+}
+\end{lstlisting}
+^D
+[CodeBlock ("lst:Hello-World",["java"],[("language","Java"),("escapechar","|"),("caption","Java Example"),("label","lst:Hello-World")]) "public class World {\n public static void main(String[] args) {\n System.out.println(\"Hello World\");\n }\n}"]
+```
diff --git a/test/command/parse-raw.md b/test/command/parse-raw.md
index f4e493c69..6c91c2fa9 100644
--- a/test/command/parse-raw.md
+++ b/test/command/parse-raw.md
@@ -9,6 +9,7 @@
% pandoc -f latex -t markdown
\emph{Hi \foo{there}}
^D
+[warning] Skipped '\foo{there}' at line 1 column 21
*Hi*
```
@@ -23,5 +24,7 @@
% pandoc -f html -t markdown
<em>Hi <blink>there</blink></em>
^D
+[warning] Skipped '<blink>' at input line 1 column 8
+[warning] Skipped '</blink>' at input line 1 column 20
*Hi there*
```
diff --git a/test/command/svg.md b/test/command/svg.md
new file mode 100644
index 000000000..b48745f9a
--- /dev/null
+++ b/test/command/svg.md
@@ -0,0 +1,132 @@
+```
+% pandoc -f latex -t icml
+\includegraphics{command/corrupt.svg}
+^D
+[warning] Could not determine image size for 'command/corrupt.svg': could not determine image type
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 150 -100">
+ <Properties>
+ <PathGeometry>
+ <GeometryPathType PathOpen="false">
+ <PathPointArray>
+ <PathPointType Anchor="-150 -100" LeftDirection="-150 -100" RightDirection="-150 -100" />
+ <PathPointType Anchor="-150 100" LeftDirection="-150 100" RightDirection="-150 100" />
+ <PathPointType Anchor="150 100" LeftDirection="150 100" RightDirection="150 100" />
+ <PathPointType Anchor="150 -100" LeftDirection="150 -100" RightDirection="150 -100" />
+ </PathPointArray>
+ </GeometryPathType>
+ </PathGeometry>
+ </Properties>
+ <Image Self="ue6" ItemTransform="1 0 0 1 -150 -100">
+ <Properties>
+ <Profile type="string">
+ $ID/Embedded
+ </Profile>
+ </Properties>
+ <Link Self="ueb" LinkResourceURI="file:command/corrupt.svg" />
+ </Image>
+ </Rectangle>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+```
+
+```
+% pandoc -f latex -t icml
+\includegraphics{command/SVG_logo.svg}
+^D
+[warning] Could not determine image size for 'command/SVG_logo.svg': could not determine SVG size
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 150 -100">
+ <Properties>
+ <PathGeometry>
+ <GeometryPathType PathOpen="false">
+ <PathPointArray>
+ <PathPointType Anchor="-150 -100" LeftDirection="-150 -100" RightDirection="-150 -100" />
+ <PathPointType Anchor="-150 100" LeftDirection="-150 100" RightDirection="-150 100" />
+ <PathPointType Anchor="150 100" LeftDirection="150 100" RightDirection="150 100" />
+ <PathPointType Anchor="150 -100" LeftDirection="150 -100" RightDirection="150 -100" />
+ </PathPointArray>
+ </GeometryPathType>
+ </PathGeometry>
+ </Properties>
+ <Image Self="ue6" ItemTransform="1 0 0 1 -150 -100">
+ <Properties>
+ <Profile type="string">
+ $ID/Embedded
+ </Profile>
+ </Properties>
+ <Link Self="ueb" LinkResourceURI="file:command/SVG_logo.svg" />
+ </Image>
+ </Rectangle>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+```
+
+```
+% pandoc -f latex -t icml
+\includegraphics{command/SVG_logo-without-xml-declaration.svg}
+^D
+[warning] Could not determine image size for 'command/SVG_logo-without-xml-declaration.svg': could not determine SVG size
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 150 -100">
+ <Properties>
+ <PathGeometry>
+ <GeometryPathType PathOpen="false">
+ <PathPointArray>
+ <PathPointType Anchor="-150 -100" LeftDirection="-150 -100" RightDirection="-150 -100" />
+ <PathPointType Anchor="-150 100" LeftDirection="-150 100" RightDirection="-150 100" />
+ <PathPointType Anchor="150 100" LeftDirection="150 100" RightDirection="150 100" />
+ <PathPointType Anchor="150 -100" LeftDirection="150 -100" RightDirection="150 -100" />
+ </PathPointArray>
+ </GeometryPathType>
+ </PathGeometry>
+ </Properties>
+ <Image Self="ue6" ItemTransform="1 0 0 1 -150 -100">
+ <Properties>
+ <Profile type="string">
+ $ID/Embedded
+ </Profile>
+ </Properties>
+ <Link Self="ueb" LinkResourceURI="file:command/SVG_logo-without-xml-declaration.svg" />
+ </Image>
+ </Rectangle>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+```
+
+
+```
+% pandoc -f latex -t icml
+\includegraphics{command/inkscape-cube.svg}
+^D
+<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
+ <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 54.75 -65.25">
+ <Properties>
+ <PathGeometry>
+ <GeometryPathType PathOpen="false">
+ <PathPointArray>
+ <PathPointType Anchor="-54.75 -65.25" LeftDirection="-54.75 -65.25" RightDirection="-54.75 -65.25" />
+ <PathPointType Anchor="-54.75 65.25" LeftDirection="-54.75 65.25" RightDirection="-54.75 65.25" />
+ <PathPointType Anchor="54.75 65.25" LeftDirection="54.75 65.25" RightDirection="54.75 65.25" />
+ <PathPointType Anchor="54.75 -65.25" LeftDirection="54.75 -65.25" RightDirection="54.75 -65.25" />
+ </PathPointArray>
+ </GeometryPathType>
+ </PathGeometry>
+ </Properties>
+ <Image Self="ue6" ItemTransform="1 0 0 1 -54.75 -65.25">
+ <Properties>
+ <Profile type="string">
+ $ID/Embedded
+ </Profile>
+ </Properties>
+ <Link Self="ueb" LinkResourceURI="file:command/inkscape-cube.svg" />
+ </Image>
+ </Rectangle>
+ </CharacterStyleRange>
+</ParagraphStyleRange>
+```
+
diff --git a/test/command/tabularx.md b/test/command/tabularx.md
new file mode 100644
index 000000000..bf7670e9c
--- /dev/null
+++ b/test/command/tabularx.md
@@ -0,0 +1,110 @@
+```
+% pandoc -f latex -t native --quiet
+\begin{tabularx}{\linewidth}{|c|c|c|}
+\hline
+ Column Heading 1
+ & Column Heading 2
+ & Column Heading 3 \\
+\hline
+ Cell 1.1
+ & Cell 1.2
+ & Cell 1.3 \\
+\hline
+ Cell 2.1
+ & Cell 2.2
+ & Cell 2.3 \\
+\hline
+ Cell 3.1
+ & Cell 3.2
+ & Cell 3.3 \\
+\hline
+\end{tabularx}
+^D
+[Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0]
+ [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
+ [[[Plain [Str "Cell",Space,Str "1.1"]]
+ ,[Plain [Str "Cell",Space,Str "1.2"]]
+ ,[Plain [Str "Cell",Space,Str "1.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "2.1"]]
+ ,[Plain [Str "Cell",Space,Str "2.2"]]
+ ,[Plain [Str "Cell",Space,Str "2.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "3.1"]]
+ ,[Plain [Str "Cell",Space,Str "3.2"]]
+ ,[Plain [Str "Cell",Space,Str "3.3"]]]]]
+```
+
+```
+% pandoc -f latex -t native --quiet
+\begin{tabularx}{\linewidth}{|X|c|p{0.25\linewidth}|}
+\hline
+ Column Heading 1
+ & Column Heading 2
+ & Column Heading 3 \\
+\hline
+ Cell 1.1
+ & Cell 1.2
+ & Cell 1.3 \\
+\hline
+ Cell 2.1
+ & Cell 2.2
+ & Cell 2.3 \\
+\hline
+ Cell 3.1
+ & Cell 3.2
+ & Cell 3.3 \\
+\hline
+\end{tabularx}
+^D
+[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.25]
+ [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
+ [[[Plain [Str "Cell",Space,Str "1.1"]]
+ ,[Plain [Str "Cell",Space,Str "1.2"]]
+ ,[Plain [Str "Cell",Space,Str "1.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "2.1"]]
+ ,[Plain [Str "Cell",Space,Str "2.2"]]
+ ,[Plain [Str "Cell",Space,Str "2.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "3.1"]]
+ ,[Plain [Str "Cell",Space,Str "3.2"]]
+ ,[Plain [Str "Cell",Space,Str "3.3"]]]]]
+```
+
+```
+% pandoc -f latex -t native --quiet
+\begin{tabularx}{\linewidth}{|b{0.25\linewidth}|c|m{0.25\linewidth}|}
+\hline
+ Column Heading 1
+ & Column Heading 2
+ & Column Heading 3 \\
+\hline
+ Cell 1.1
+ & Cell 1.2
+ & Cell 1.3 \\
+\hline
+ Cell 2.1
+ & Cell 2.2
+ & Cell 2.3 \\
+\hline
+ Cell 3.1
+ & Cell 3.2
+ & Cell 3.3 \\
+\hline
+\end{tabularx}
+^D
+[Table [] [AlignLeft,AlignCenter,AlignLeft] [0.25,0.0,0.25]
+ [[Plain [Str "Column",Space,Str "Heading",Space,Str "1"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "2"]]
+ ,[Plain [Str "Column",Space,Str "Heading",Space,Str "3"]]]
+ [[[Plain [Str "Cell",Space,Str "1.1"]]
+ ,[Plain [Str "Cell",Space,Str "1.2"]]
+ ,[Plain [Str "Cell",Space,Str "1.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "2.1"]]
+ ,[Plain [Str "Cell",Space,Str "2.2"]]
+ ,[Plain [Str "Cell",Space,Str "2.3"]]]
+ ,[[Plain [Str "Cell",Space,Str "3.1"]]
+ ,[Plain [Str "Cell",Space,Str "3.2"]]
+ ,[Plain [Str "Cell",Space,Str "3.3"]]]]]
+```
diff --git a/test/fb2/titles.fb2 b/test/fb2/titles.fb2
index 9e8d47e36..0a3b1404e 100644
--- a/test/fb2/titles.fb2
+++ b/test/fb2/titles.fb2
@@ -1,3 +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>
+<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></body></FictionBook>
diff --git a/test/fb2/titles.markdown b/test/fb2/titles.markdown
index cc3d0e0d0..1eaf2ccd5 100644
--- a/test/fb2/titles.markdown
+++ b/test/fb2/titles.markdown
@@ -4,7 +4,3 @@ This example tests if Pandoc doesn't insert forbidden elements in FictionBook ti
# *Emphasized* **Strong** Title
-# Title with\
-line break
-
-
diff --git a/test/latex-reader.native b/test/latex-reader.native
index f37f1b2ca..d481a714d 100644
--- a/test/latex-reader.native
+++ b/test/latex-reader.native
@@ -249,10 +249,10 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",SoftBreak,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a",Math InlineMath "\\sim",Str "b",SoftBreak,Str "c",Math InlineMath "\\sim",Str "d."]
,HorizontalRule
,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
-,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
+,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Str "\8198",Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
-,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
+,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."],Str "\8198"],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",SoftBreak,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two\8212three\8212four\8212five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
diff --git a/test/lhs-test.latex b/test/lhs-test.latex
index 3ca8f97c8..027ad3a0e 100644
--- a/test/lhs-test.latex
+++ b/test/lhs-test.latex
@@ -17,6 +17,12 @@
\usepackage[]{microtype}
\UseMicrotypeSet[protrusion]{basicmath} % disable protrusion for tt fonts
}{}
+\IfFileExists{parskip.sty}{%
+\usepackage{parskip}
+}{% else
+\setlength{\parindent}{0pt}
+\setlength{\parskip}{6pt plus 2pt minus 1pt}
+}
\PassOptionsToPackage{hyphens}{url} % url is loaded by hyperref
\usepackage[unicode=true]{hyperref}
\hypersetup{
@@ -61,12 +67,6 @@
\newcommand{\AlertTok}[1]{\textcolor[rgb]{1.00,0.00,0.00}{\textbf{#1}}}
\newcommand{\ErrorTok}[1]{\textcolor[rgb]{1.00,0.00,0.00}{\textbf{#1}}}
\newcommand{\NormalTok}[1]{#1}
-\IfFileExists{parskip.sty}{%
-\usepackage{parskip}
-}{% else
-\setlength{\parindent}{0pt}
-\setlength{\parskip}{6pt plus 2pt minus 1pt}
-}
\setlength{\emergencystretch}{3em} % prevent overfull lines
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
diff --git a/test/lhs-test.latex+lhs b/test/lhs-test.latex+lhs
index b0a58ac78..4aac4c7bb 100644
--- a/test/lhs-test.latex+lhs
+++ b/test/lhs-test.latex+lhs
@@ -17,6 +17,12 @@
\usepackage[]{microtype}
\UseMicrotypeSet[protrusion]{basicmath} % disable protrusion for tt fonts
}{}
+\IfFileExists{parskip.sty}{%
+\usepackage{parskip}
+}{% else
+\setlength{\parindent}{0pt}
+\setlength{\parskip}{6pt plus 2pt minus 1pt}
+}
\PassOptionsToPackage{hyphens}{url} % url is loaded by hyperref
\usepackage[unicode=true]{hyperref}
\hypersetup{
@@ -26,12 +32,6 @@
\usepackage{listings}
\newcommand{\passthrough}[1]{#1}
\lstnewenvironment{code}{\lstset{language=Haskell,basicstyle=\small\ttfamily}}{}
-\IfFileExists{parskip.sty}{%
-\usepackage{parskip}
-}{% else
-\setlength{\parindent}{0pt}
-\setlength{\parskip}{6pt plus 2pt minus 1pt}
-}
\setlength{\emergencystretch}{3em} % prevent overfull lines
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native
index baafb5334..1007dbac7 100644
--- a/test/markdown-reader-more.native
+++ b/test/markdown-reader-more.native
@@ -99,74 +99,74 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
[[Plain [Str "col",Space,Str "1"]]
,[Plain [Str "col",Space,Str "2"]]
,[Plain [Str "col",Space,Str "3"]]]
- [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
- ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
- ,[[Para [Str "r2",Space,Str "d"]]
- ,[Para [Str "e"]]
- ,[Para [Str "f"]]]]
+ [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
+ ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
+ ,[[Plain [Str "r2",Space,Str "d"]]
+ ,[Plain [Str "e"]]
+ ,[Plain [Str "f"]]]]
,Para [Str "Headless"]
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
[[]
,[]
,[]]
- [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
- ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
- ,[[Para [Str "r2",Space,Str "d"]]
- ,[Para [Str "e"]]
- ,[Para [Str "f"]]]]
+ [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
+ ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
+ ,[[Plain [Str "r2",Space,Str "d"]]
+ ,[Plain [Str "e"]]
+ ,[Plain [Str "f"]]]]
,Para [Str "With",Space,Str "alignments"]
,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
[[Plain [Str "col",Space,Str "1"]]
,[Plain [Str "col",Space,Str "2"]]
,[Plain [Str "col",Space,Str "3"]]]
- [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
- ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
- ,[[Para [Str "r2",Space,Str "d"]]
- ,[Para [Str "e"]]
- ,[Para [Str "f"]]]]
+ [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
+ ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
+ ,[[Plain [Str "r2",Space,Str "d"]]
+ ,[Plain [Str "e"]]
+ ,[Plain [Str "f"]]]]
,Para [Str "Headless",Space,Str "with",Space,Str "alignments"]
,Table [] [AlignRight,AlignLeft,AlignCenter] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
[[]
,[]
,[]]
- [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
- ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
- ,[[Para [Str "r2",Space,Str "d"]]
- ,[Para [Str "e"]]
- ,[Para [Str "f"]]]]
+ [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
+ ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
+ ,[[Plain [Str "r2",Space,Str "d"]]
+ ,[Plain [Str "e"]]
+ ,[Plain [Str "f"]]]]
,Para [Str "Spaces",Space,Str "at",Space,Str "ends",Space,Str "of",Space,Str "lines"]
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
[[]
,[]
,[]]
- [[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
- ,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
- ,[[Para [Str "r2",Space,Str "d"]]
- ,[Para [Str "e"]]
- ,[Para [Str "f"]]]]
+ [[[Plain [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
+ ,[Plain [Str "b",SoftBreak,Str "b",Space,Str "2"]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
+ ,[[Plain [Str "r2",Space,Str "d"]]
+ ,[Plain [Str "e"]]
+ ,[Plain [Str "f"]]]]
,Para [Str "Multiple",Space,Str "blocks",Space,Str "in",Space,Str "a",Space,Str "cell"]
,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555]
[[]
,[]
,[]]
[[[Header 1 ("col-1",[],[]) [Str "col",Space,Str "1"]
- ,Para [Str "col",Space,Str "1"]]
+ ,Plain [Str "col",Space,Str "1"]]
,[Header 1 ("col-2",[],[]) [Str "col",Space,Str "2"]
- ,Para [Str "col",Space,Str "2"]]
+ ,Plain [Str "col",Space,Str "2"]]
,[Header 1 ("col-3",[],[]) [Str "col",Space,Str "3"]
- ,Para [Str "col",Space,Str "3"]]]
+ ,Plain [Str "col",Space,Str "3"]]]
,[[Para [Str "r1",Space,Str "a"]
,Para [Str "r1",Space,Str "bis"]]
,[BulletList
[[Plain [Str "b"]]
,[Plain [Str "b",Space,Str "2"]]
,[Plain [Str "b",Space,Str "2"]]]]
- ,[Para [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]]
+ ,[Plain [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]]
,Para [Str "Empty",Space,Str "cells"]
,Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
[[]
diff --git a/test/tables-rstsubset.native b/test/tables-rstsubset.native
index d9bb9f2fb..8b7ccdf76 100644
--- a/test/tables-rstsubset.native
+++ b/test/tables-rstsubset.native
@@ -54,9 +54,9 @@
,[Plain [Str "1"]]]]
,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"]
,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325]
- [[Plain [Str "Centered",Space,Str "Header"]]
- ,[Plain [Str "Left",Space,Str "Aligned"]]
- ,[Plain [Str "Right",Space,Str "Aligned"]]
+ [[Plain [Str "Centered",SoftBreak,Str "Header"]]
+ ,[Plain [Str "Left",SoftBreak,Str "Aligned"]]
+ ,[Plain [Str "Right",SoftBreak,Str "Aligned"]]
,[Plain [Str "Default",Space,Str "aligned"]]]
[[[Plain [Str "First"]]
,[Plain [Str "row"]]
@@ -68,9 +68,9 @@
,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",SoftBreak,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",SoftBreak,Str "between",Space,Str "rows."]]]]
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"]
,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1375,0.125,0.15,0.325]
- [[Plain [Str "Centered",Space,Str "Header"]]
- ,[Plain [Str "Left",Space,Str "Aligned"]]
- ,[Plain [Str "Right",Space,Str "Aligned"]]
+ [[Plain [Str "Centered",SoftBreak,Str "Header"]]
+ ,[Plain [Str "Left",SoftBreak,Str "Aligned"]]
+ ,[Plain [Str "Right",SoftBreak,Str "Aligned"]]
,[Plain [Str "Default",Space,Str "aligned"]]]
[[[Plain [Str "First"]]
,[Plain [Str "row"]]
diff --git a/test/tables.muse b/test/tables.muse
index afdccd476..fdf20be49 100644
--- a/test/tables.muse
+++ b/test/tables.muse
@@ -1,46 +1,46 @@
Simple table with caption:
-Right || Left || Center || Default
-12 | 12 | 12 | 12
-123 | 123 | 123 | 123
-1 | 1 | 1 | 1
-|+ Demonstration of simple table syntax. +|
+ Right || Left || Center || Default
+ 12 | 12 | 12 | 12
+ 123 | 123 | 123 | 123
+ 1 | 1 | 1 | 1
+ |+ Demonstration of simple table syntax. +|
Simple table without caption:
-Right || Left || Center || Default
-12 | 12 | 12 | 12
-123 | 123 | 123 | 123
-1 | 1 | 1 | 1
+ Right || Left || Center || Default
+ 12 | 12 | 12 | 12
+ 123 | 123 | 123 | 123
+ 1 | 1 | 1 | 1
Simple table indented two spaces:
-Right || Left || Center || Default
-12 | 12 | 12 | 12
-123 | 123 | 123 | 123
-1 | 1 | 1 | 1
-|+ Demonstration of simple table syntax. +|
+ Right || Left || Center || Default
+ 12 | 12 | 12 | 12
+ 123 | 123 | 123 | 123
+ 1 | 1 | 1 | 1
+ |+ Demonstration of simple table syntax. +|
Multiline table with 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.
-|+ 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.
+ |+ Here’s the caption. It may span multiple lines. +|
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.
+ 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.
Table without column headers:
-12 | 12 | 12 | 12
-123 | 123 | 123 | 123
-1 | 1 | 1 | 1
+ 12 | 12 | 12 | 12
+ 123 | 123 | 123 | 123
+ 1 | 1 | 1 | 1
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.
+ 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.
diff --git a/test/testsuite.native b/test/testsuite.native
index fa234dfc2..0587bddb8 100644
--- a/test/testsuite.native
+++ b/test/testsuite.native
@@ -369,8 +369,6 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
-,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
-,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
diff --git a/test/testsuite.txt b/test/testsuite.txt
index f6b0a7c95..9413cc81a 100644
--- a/test/testsuite.txt
+++ b/test/testsuite.txt
@@ -621,16 +621,11 @@ Just a [URL](/url/).
## Reference
-Foo [bar] [a].
-
Foo [bar][a].
-Foo [bar]
-[a].
-
[a]: /url/
-With [embedded [brackets]] [b].
+With [embedded [brackets]][b].
[b] by itself should be a link.
@@ -659,9 +654,9 @@ Foo [biz](/url/ "Title with "quote" inside").
## With ampersands
-Here's a [link with an ampersand in the URL] [1].
+Here's a [link with an ampersand in the URL][1].
-Here's a link with an amersand in the link text: [AT&T] [2].
+Here's a link with an amersand in the link text: [AT&T][2].
Here's an [inline link](/script?foo=1&bar=2).
diff --git a/test/writer.asciidoc b/test/writer.asciidoc
index 2bf62e36f..639663743 100644
--- a/test/writer.asciidoc
+++ b/test/writer.asciidoc
@@ -600,10 +600,6 @@ Reference
Foo link:/url/[bar].
-Foo link:/url/[bar].
-
-Foo link:/url/[bar].
-
With link:/url/[embedded [brackets]].
link:/url/[b] by itself should be a link.
diff --git a/test/writer.context b/test/writer.context
index 04df66178..9884c82c9 100644
--- a/test/writer.context
+++ b/test/writer.context
@@ -6,19 +6,28 @@
style=,
color=,
contrastcolor=]
+
% make chapter, section bookmarks visible when opening document
\placebookmarks[chapter, section, subsection, subsubsection, subsubsubsection, subsubsubsubsection][chapter, section]
\setupinteractionscreen[option=bookmark]
\setuptagging[state=start]
+
% use microtypography
\definefontfeature[default][default][script=latn, protrusion=quality, expansion=quality, itlc=yes, textitalics=yes, onum=yes, pnum=yes]
\definefontfeature[smallcaps][script=latn, protrusion=quality, expansion=quality, smcp=yes, onum=yes, pnum=yes]
\setupalign[hz,hanging]
\setupitaliccorrection[global, always]
+
\setupbodyfontenvironment[default][em=italic] % use italic as em, not slanted
-\usemodule[simplefonts]
-\setmainfontfallback[DejaVu Serif][range={greekandcoptic, greekextended}, force=yes, rscale=auto]
+
+\definefallbackfamily[mainface][rm][DejaVu Serif][preset=range:greek, force=yes]
+\definefontfamily[mainface][rm][Latin Modern Roman]
+\definefontfamily[mainface][mm][Latin Modern Math]
+\definefontfamily[mainface][ss][Latin Modern Sans]
+\definefontfamily[mainface][tt][Latin Modern Typewriter][features=none]
+\setupbodyfont[mainface]
+
\setupwhitespace[medium]
\setuphead[chapter] [style=\tfd,header=empty]
@@ -778,19 +787,15 @@ Just a \useURL[url4][/url/][][URL]\from[url4].
Foo \useURL[url13][/url/][][bar]\from[url13].
-Foo \useURL[url14][/url/][][bar]\from[url14].
-
-Foo \useURL[url15][/url/][][bar]\from[url15].
-
-With \useURL[url16][/url/][][embedded {[}brackets{]}]\from[url16].
+With \useURL[url14][/url/][][embedded {[}brackets{]}]\from[url14].
-\useURL[url17][/url/][][b]\from[url17] by itself should be a link.
+\useURL[url15][/url/][][b]\from[url15] by itself should be a link.
-Indented \useURL[url18][/url][][once]\from[url18].
+Indented \useURL[url16][/url][][once]\from[url16].
-Indented \useURL[url19][/url][][twice]\from[url19].
+Indented \useURL[url17][/url][][twice]\from[url17].
-Indented \useURL[url20][/url][][thrice]\from[url20].
+Indented \useURL[url18][/url][][thrice]\from[url18].
This should {[}not{]}{[}{]} be a link.
@@ -798,41 +803,41 @@ This should {[}not{]}{[}{]} be a link.
[not]: /url
\stoptyping
-Foo \useURL[url21][/url/][][bar]\from[url21].
+Foo \useURL[url19][/url/][][bar]\from[url19].
-Foo \useURL[url22][/url/][][biz]\from[url22].
+Foo \useURL[url20][/url/][][biz]\from[url20].
\subsection[with-ampersands]{With ampersands}
-Here's a \useURL[url23][http://example.com/?foo=1&bar=2][][link with an
-ampersand in the URL]\from[url23].
+Here's a \useURL[url21][http://example.com/?foo=1&bar=2][][link with an
+ampersand in the URL]\from[url21].
Here's a link with an amersand in the link text:
-\useURL[url24][http://att.com/][][AT&T]\from[url24].
+\useURL[url22][http://att.com/][][AT&T]\from[url22].
-Here's an \useURL[url25][/script?foo=1&bar=2][][inline link]\from[url25].
+Here's an \useURL[url23][/script?foo=1&bar=2][][inline link]\from[url23].
-Here's an \useURL[url26][/script?foo=1&bar=2][][inline link in pointy
-braces]\from[url26].
+Here's an \useURL[url24][/script?foo=1&bar=2][][inline link in pointy
+braces]\from[url24].
\subsection[autolinks]{Autolinks}
-With an ampersand: \useURL[url27][http://example.com/?foo=1&bar=2]\from[url27]
+With an ampersand: \useURL[url25][http://example.com/?foo=1&bar=2]\from[url25]
\startitemize[packed]
\item
In a list?
\item
- \useURL[url28][http://example.com/]\from[url28]
+ \useURL[url26][http://example.com/]\from[url26]
\item
It should.
\stopitemize
An e-mail address:
-\useURL[url29][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[url29]
+\useURL[url27][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[url27]
\startblockquote
-Blockquoted: \useURL[url30][http://example.com/]\from[url30]
+Blockquoted: \useURL[url28][http://example.com/]\from[url28]
\stopblockquote
Auto-links should not occur here: \type{<http://example.com/>}
@@ -871,7 +876,7 @@ Here is a footnote reference,\footnote{Here is the footnote. It can go
indent the first line of each block.\stopbuffer\footnote{\getbuffer} This
should {\em not} be a footnote reference, because it contains a space.{[}^my
note{]} Here is an inline note.\footnote{This is {\em easier} to type. Inline
- notes may contain \useURL[url31][http://google.com][][links]\from[url31] and
+ notes may contain \useURL[url29][http://google.com][][links]\from[url29] and
\type{]} verbatim characters, as well as {[}bracketed text{]}.}
\startblockquote
diff --git a/test/writer.docbook4 b/test/writer.docbook4
index eee19cdd9..163255974 100644
--- a/test/writer.docbook4
+++ b/test/writer.docbook4
@@ -1249,12 +1249,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{
Foo <ulink url="/url/">bar</ulink>.
</para>
<para>
- Foo <ulink url="/url/">bar</ulink>.
- </para>
- <para>
- Foo <ulink url="/url/">bar</ulink>.
- </para>
- <para>
With <ulink url="/url/">embedded [brackets]</ulink>.
</para>
<para>
diff --git a/test/writer.docbook5 b/test/writer.docbook5
index 07ca0f827..992cd8b63 100644
--- a/test/writer.docbook5
+++ b/test/writer.docbook5
@@ -1224,12 +1224,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{
Foo <link xlink:href="/url/">bar</link>.
</para>
<para>
- Foo <link xlink:href="/url/">bar</link>.
- </para>
- <para>
- Foo <link xlink:href="/url/">bar</link>.
- </para>
- <para>
With <link xlink:href="/url/">embedded [brackets]</link>.
</para>
<para>
diff --git a/test/writer.dokuwiki b/test/writer.dokuwiki
index 79fcdde8a..4ba1b7054 100644
--- a/test/writer.dokuwiki
+++ b/test/writer.dokuwiki
@@ -556,10 +556,6 @@ Just a [[url/|URL]].
Foo [[url/|bar]].
-Foo [[url/|bar]].
-
-Foo [[url/|bar]].
-
With [[url/|embedded [brackets]]].
[[url/|b]] by itself should be a link.
diff --git a/test/writer.fb2 b/test/writer.fb2
index 0412c8cf4..63d0bdfbf 100644
--- a/test/writer.fb2
+++ b/test/writer.fb2
@@ -1,3 +1,1013 @@
<?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><book-title>Pandoc Test Suite</book-title><author><first-name>John</first-name><last-name>MacFarlane</last-name></author><author><nickname>Anonymous</nickname></author><date>July 17, 2006</date></title-info><document-info><program-used>pandoc</program-used></document-info></description><body><title><p>Pandoc Test Suite</p></title><annotation><p>John MacFarlane</p><p>Anonymous</p><p>July 17, 2006</p></annotation><section><p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Headers</p></title><section><title><p>Level 2 with an embedded link &lt;/url&gt;</p></title><section><title><p>Level 3 with emphasis</p></title><section><title><p>Level 4</p></title><section><title><p>Level 5</p></title></section></section></section></section></section><section><title><p>Level 1</p></title><section><title><p>Level 2 with emphasis</p></title><section><title><p>Level 3</p></title><p>with no blank line</p></section></section><section><title><p>Level 2</p></title><p>with no blank line</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Paragraphs</p></title><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<empty-line />here.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Block Quotes</p></title><p>E-mail style:</p><cite><p>This is a block quote. It is pretty short.</p></cite><cite><p>Code in a block quote:</p><empty-line /><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><empty-line /><p>A list:</p><p> 1. item one</p><p> 2. item two</p><p>Nested block quotes:</p><cite><p>nested</p></cite><cite><p>nested</p></cite></cite><p>This should not be a block quote: 2 &gt; 1.</p><p>And a following paragraph.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Code Blocks</p></title><p>Code:</p><empty-line /><p><code>---- (should be four hyphens)</code></p><p><code></code></p><p><code>sub status {</code></p><p><code> print &quot;working&quot;;</code></p><p><code>}</code></p><p><code></code></p><p><code>this code block is indented by one tab</code></p><empty-line /><p>And:</p><empty-line /><p><code> this code block is indented by two tabs</code></p><p><code></code></p><p><code>These should not be escaped: \$ \\ \&gt; \[ \{</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Lists</p></title><section><title><p>Unordered</p></title><p>Asterisks tight:</p><p>• asterisk 1</p><p>• asterisk 2</p><p>• asterisk 3</p><p>Asterisks loose:</p><p>• asterisk 1<empty-line /></p><p>• asterisk 2<empty-line /></p><p>• asterisk 3<empty-line /></p><p>Pluses tight:</p><p>• Plus 1</p><p>• Plus 2</p><p>• Plus 3</p><p>Pluses loose:</p><p>• Plus 1<empty-line /></p><p>• Plus 2<empty-line /></p><p>• Plus 3<empty-line /></p><p>Minuses tight:</p><p>• Minus 1</p><p>• Minus 2</p><p>• Minus 3</p><p>Minuses loose:</p><p>• Minus 1<empty-line /></p><p>• Minus 2<empty-line /></p><p>• Minus 3<empty-line /></p></section><section><title><p>Ordered</p></title><p>Tight:</p><p> 1. First</p><p> 2. Second</p><p> 3. Third</p><p>and:</p><p> 1. One</p><p> 2. Two</p><p> 3. Three</p><p>Loose using tabs:</p><p> 1. First<empty-line /></p><p> 2. Second<empty-line /></p><p> 3. Third<empty-line /></p><p>and using spaces:</p><p> 1. One<empty-line /></p><p> 2. Two<empty-line /></p><p> 3. Three<empty-line /></p><p>Multiple paragraphs:</p><p> 1. Item 1, graf one.<empty-line />Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.<empty-line /></p><p> 2. Item 2.<empty-line /></p><p> 3. Item 3.<empty-line /></p></section><section><title><p>Nested</p></title><p>• Tab<p>◦ Tab<p>* Tab</p></p></p><p>Here’s another:</p><p> 1. First</p><p> 2. Second:<p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third</p><p>Same thing but with paragraphs:</p><p> 1. First<empty-line /></p><p> 2. Second:<empty-line /><p>   • Fee</p><p>   • Fie</p><p>   • Foe</p></p><p> 3. Third<empty-line /></p></section><section><title><p>Tabs and spaces</p></title><p>• this is a list item indented with tabs<empty-line /></p><p>• this is a list item indented with spaces<empty-line /><p>◦ this is an example list item indented with tabs<empty-line /></p><p>◦ this is an example list item indented with spaces<empty-line /></p></p></section><section><title><p>Fancy list markers</p></title><p> (2) begins with 2</p><p> (3) and now 3<empty-line />with a continuation<empty-line /><p> (3) iv. sublist with roman numerals, starting with 4</p><p> (3) v. more items<p> (3) v. (A) a subsublist</p><p> (3) v. (B) a subsublist</p></p></p><p>Nesting:</p><p> A. Upper Alpha<p> A. I. Upper Roman.<p> A. I. (6) Decimal start with 6<p> A. I. (6) c) Lower alpha with paren</p></p></p></p><p>Autonumbering:</p><p> 1. Autonumber.</p><p> 2. More.<p> 2. 1. Nested.</p></p><p>Should not be a list item:</p><p>M.A. 2007</p><p>B. Williams</p><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Definition Lists</p></title><p>Tight using spaces:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Tight using tabs:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /></p><p><strong>banana</strong></p><p>    yellow fruit<empty-line /></p><p>Multiple blocks with italics:</p><p><strong><emphasis>apple</emphasis></strong></p><p>    red fruit<empty-line />    contains seeds, crisp, pleasant to taste<empty-line /></p><p><strong><emphasis>orange</emphasis></strong></p><p>    orange fruit<empty-line /><empty-line /><p><code>    { orange code block }</code></p><empty-line /><cite><p>    orange block quote</p></cite></p><p>Multiple definitions, tight:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Multiple definitions, loose:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line />    bank<empty-line /></p><p>Blank line after term, indented marker, alternate markers:</p><p><strong>apple</strong></p><p>    red fruit<empty-line />    computer<empty-line /></p><p><strong>orange</strong></p><p>    orange fruit<empty-line /><p> 1. sublist</p><p> 2. sublist</p></p></section><section><title><p>HTML Blocks</p></title><p>Simple block on one line:</p>foo<p>And nested without indentation:</p><p>foo</p>bar<p>Interpreted markdown in a table:</p>This is <emphasis>emphasized</emphasis>And this is <strong>strong</strong><p>Here’s a simple block:</p><p>foo</p><p>This should be a code block, though:</p><empty-line /><p><code>&lt;div&gt;</code></p><p><code> foo</code></p><p><code>&lt;/div&gt;</code></p><empty-line /><p>As should this:</p><empty-line /><p><code>&lt;div&gt;foo&lt;/div&gt;</code></p><empty-line /><p>Now, nested:</p>foo<p>This should just be an HTML comment:</p><p>Multiline:</p><p>Code block:</p><empty-line /><p><code>&lt;!-- Comment --&gt;</code></p><empty-line /><p>Just plain comment, with trailing spaces on the line:</p><p>Code:</p><empty-line /><p><code>&lt;hr /&gt;</code></p><empty-line /><p>Hr’s:</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Inline Markup</p></title><p>This is <emphasis>emphasized</emphasis>, and so <emphasis>is this</emphasis>.</p><p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p><p>An <emphasis>emphasized link<a l:href="#l1" type="note"><sup>[1]</sup></a></emphasis>.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p><strong><emphasis>This is strong and em.</emphasis></strong></p><p>So is <strong><emphasis>this</emphasis></strong> word.</p><p>This is code: <code>&gt;</code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code>&lt;html&gt;</code>.</p><p><strikethrough>This is <emphasis>strikeout</emphasis>.</strikethrough></p><p>Superscripts: a<sup>bc</sup>d a<sup><emphasis>hello</emphasis></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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Smart quotes, ellipses, dashes</p></title><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 “quoted link<a l:href="#l2" type="note"><sup>[2]</sup></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><empty-line /><p>——————————</p><empty-line /></section><section><title><p>LaTeX</p></title><p>• </p><p>• <code>2+2=4</code></p><p>• <code>x \in y</code></p><p>• <code>\alpha \wedge \omega</code></p><p>• <code>223</code></p><p>• <code>p</code>-Tree</p><p>• Here’s some display math: <code>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</code></p><p>• Here’s one that has a line break in it: <code>\alpha + \omega \times x^2</code>.</p><p>These shouldn’t be math:</p><p>• To get the famous equation, write <code>$e = mc^2$</code>.</p><p>• $22,000 is a <emphasis>lot</emphasis> of money. So is $34,000. (It worked if “lot” is emphasized.)</p><p>• Shoes ($20) and socks ($5).</p><p>• Escaped <code>$</code>: $73 <emphasis>this should be emphasized</emphasis> 23$.</p><p>Here’s a LaTeX table:</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Special Characters</p></title><p>Here is some unicode:</p><p>• I hat: Î</p><p>• o umlaut: ö</p><p>• section: §</p><p>• set membership: ∈</p><p>• copyright: ©</p><p>AT&amp;T has an ampersand in their name.</p><p>AT&amp;T is another way to write it.</p><p>This &amp; that.</p><p>4 &lt; 5.</p><p>6 &gt; 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: &gt;</p><p>Hash: #</p><p>Period: .</p><p>Bang: !</p><p>Plus: +</p><p>Minus: -</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Links</p></title><section><title><p>Explicit</p></title><p>Just a URL<a l:href="#l3" type="note"><sup>[3]</sup></a>.</p><p>URL and title<a l:href="#l4" type="note"><sup>[4]</sup></a>.</p><p>URL and title<a l:href="#l5" type="note"><sup>[5]</sup></a>.</p><p>URL and title<a l:href="#l6" type="note"><sup>[6]</sup></a>.</p><p>URL and title<a l:href="#l7" type="note"><sup>[7]</sup></a></p><p>URL and title<a l:href="#l8" type="note"><sup>[8]</sup></a></p><p>with_underscore<a l:href="#l9" type="note"><sup>[9]</sup></a></p><p>Email link<a l:href="#l10" type="note"><sup>[10]</sup></a></p><p>Empty<a l:href="#l11" type="note"><sup>[11]</sup></a>.</p></section><section><title><p>Reference</p></title><p>Foo bar<a l:href="#l12" type="note"><sup>[12]</sup></a>.</p><p>Foo bar<a l:href="#l13" type="note"><sup>[13]</sup></a>.</p><p>Foo bar<a l:href="#l14" type="note"><sup>[14]</sup></a>.</p><p>With embedded [brackets]<a l:href="#l15" type="note"><sup>[15]</sup></a>.</p><p>b<a l:href="#l16" type="note"><sup>[16]</sup></a> by itself should be a link.</p><p>Indented once<a l:href="#l17" type="note"><sup>[17]</sup></a>.</p><p>Indented twice<a l:href="#l18" type="note"><sup>[18]</sup></a>.</p><p>Indented thrice<a l:href="#l19" type="note"><sup>[19]</sup></a>.</p><p>This should [not][] be a link.</p><empty-line /><p><code>[not]: /url</code></p><empty-line /><p>Foo bar<a l:href="#l20" type="note"><sup>[20]</sup></a>.</p><p>Foo biz<a l:href="#l21" type="note"><sup>[21]</sup></a>.</p></section><section><title><p>With ampersands</p></title><p>Here’s a link with an ampersand in the URL<a l:href="#l22" type="note"><sup>[22]</sup></a>.</p><p>Here’s a link with an amersand in the link text: AT&amp;T<a l:href="#l23" type="note"><sup>[23]</sup></a>.</p><p>Here’s an inline link<a l:href="#l24" type="note"><sup>[24]</sup></a>.</p><p>Here’s an inline link in pointy braces<a l:href="#l25" type="note"><sup>[25]</sup></a>.</p></section><section><title><p>Autolinks</p></title><p>With an ampersand: http://example.com/?foo=1&amp;bar=2<a l:href="#l26" type="note"><sup>[26]</sup></a></p><p>• In a list?</p><p>• http://example.com/<a l:href="#l27" type="note"><sup>[27]</sup></a></p><p>• It should.</p><p>An e-mail address: nobody@nowhere.net<a l:href="#l28" type="note"><sup>[28]</sup></a></p><cite><p>Blockquoted: http://example.com/<a l:href="#l29" type="note"><sup>[29]</sup></a></p></cite><p>Auto-links should not occur here: <code>&lt;http://example.com/&gt;</code></p><empty-line /><p><code>or here: &lt;http://example.com/&gt;</code></p><empty-line /><empty-line /><p>——————————</p><empty-line /></section></section><section><title><p>Images</p></title><p>From “Voyage dans la Lune” by Georges Melies (1902):</p><image l:href="#image1" l:type="imageType" alt="lalune" title="Voyage dans la Lune" /><p>Here is a movie <image l:href="#image2" l:type="inlineImageType" alt="movie" /> icon.</p><empty-line /><p>——————————</p><empty-line /></section><section><title><p>Footnotes</p></title><p>Here is a footnote reference,<a l:href="#n30" type="note"><sup>[30]</sup></a> and another.<a l:href="#n31" type="note"><sup>[31]</sup></a> This should <emphasis>not</emphasis> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a l:href="#n32" type="note"><sup>[32]</sup></a></p><cite><p>Notes can go in quotes.<a l:href="#n33" type="note"><sup>[33]</sup></a></p></cite><p> 1. And in list items.<a l:href="#n34" type="note"><sup>[34]</sup></a></p><p>This paragraph should not be part of the note, as it is not indented.</p></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>/url</code></p></section><section id="l2"><title><p>2</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l3"><title><p>3</p></title><p><code>/url/</code></p></section><section id="l4"><title><p>4</p></title><p>title: <code>/url/</code></p></section><section id="l5"><title><p>5</p></title><p>title preceded by two spaces: <code>/url/</code></p></section><section id="l6"><title><p>6</p></title><p>title preceded by a tab: <code>/url/</code></p></section><section id="l7"><title><p>7</p></title><p>title with &quot;quotes&quot; in it: <code>/url/</code></p></section><section id="l8"><title><p>8</p></title><p>title with single quotes: <code>/url/</code></p></section><section id="l9"><title><p>9</p></title><p><code>/url/with_underscore</code></p></section><section id="l10"><title><p>10</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l11"><title><p>11</p></title><p><code></code></p></section><section id="l12"><title><p>12</p></title><p><code>/url/</code></p></section><section id="l13"><title><p>13</p></title><p><code>/url/</code></p></section><section id="l14"><title><p>14</p></title><p><code>/url/</code></p></section><section id="l15"><title><p>15</p></title><p><code>/url/</code></p></section><section id="l16"><title><p>16</p></title><p><code>/url/</code></p></section><section id="l17"><title><p>17</p></title><p><code>/url</code></p></section><section id="l18"><title><p>18</p></title><p><code>/url</code></p></section><section id="l19"><title><p>19</p></title><p><code>/url</code></p></section><section id="l20"><title><p>20</p></title><p>Title with &quot;quotes&quot; inside: <code>/url/</code></p></section><section id="l21"><title><p>21</p></title><p>Title with &quot;quote&quot; inside: <code>/url/</code></p></section><section id="l22"><title><p>22</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l23"><title><p>23</p></title><p>AT&amp;T: <code>http://att.com/</code></p></section><section id="l24"><title><p>24</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l25"><title><p>25</p></title><p><code>/script?foo=1&amp;bar=2</code></p></section><section id="l26"><title><p>26</p></title><p><code>http://example.com/?foo=1&amp;bar=2</code></p></section><section id="l27"><title><p>27</p></title><p><code>http://example.com/</code></p></section><section id="l28"><title><p>28</p></title><p><code>mailto:nobody@nowhere.net</code></p></section><section id="l29"><title><p>29</p></title><p><code>http://example.com/</code></p></section><section id="n30"><title><p>30</p></title><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</p></section><section id="n31"><title><p>31</p></title><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><empty-line /><p><code> { &lt;code&gt; }</code></p><empty-line /><p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p></section><section id="n32"><title><p>32</p></title><p>This is <emphasis>easier</emphasis> to type. Inline notes may contain links<a l:href="#l32" type="note"><sup>[32]</sup></a> and <code>]</code> verbatim characters, as well as [bracketed text].</p></section><section id="n33"><title><p>33</p></title><p>In quote.</p></section><section id="n34"><title><p>34</p></title><p>In list.</p></section></body><binary id="image2" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEASABIAAD//gBQVGhpcyBhcnQgaXMgaW4gdGhlIHB1YmxpYyBkb21haW4uIEtldmluIEh1Z2hlcywga2V2aW5oQGVpdC5jb20sIFNlcHRlbWJlciAxOTk1/9sAQwABAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/9sAQwEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEBAQEB/8AAEQgAFgAUAwEiAAIRAQMRAf/EABoAAQACAwEAAAAAAAAAAAAAAAAICQUGCgf/xAAjEAABBQEAAwABBQAAAAAAAAAGAwQFBwgCAAEJChEVOXa3/8QAFgEBAQEAAAAAAAAAAAAAAAAABggA/8QAJhEBAAECBQEJAAAAAAAAAAAAAQIAAwQFBhEhszE0NlFUcXR1tP/aAAwDAQACEQMRAD8AqQzziPNmpiqnIO1q4H+WkB84MdlzRSuM82/jVw/JCORtRmQz5d2VTy6WmS2eSYx3U/qkSRbgFsqRzH2Is4/mCluXc33vy8xTnJjTNqV/T8LKmkhr8Hq1da2aOvTfIh2CFeNt+GxFBP8AJFdFUbPWh+4FdXV7OtZOMR7mK9lBWNN+JBmMQ5cwmfH8DEFhTZUCRlE6CBq/ds/nBh9oYygeY1L9FnCUnBSN1t+w0l9bNomx1cllsOrL9OCTKtKOIqua6UVjP0dEvTyM7gp/3whbkAD0ScX3r6MLg+C2/XsMhCnJRn/5cVNHyJHiX6JKIFhhqnFeagm9BIgjfcJyNBTZiROBUk6Mp8CJRmT4NWU2MatV7n495DPk/wAbMJSRJOTBDItq0KR5s/nJN7LPW8AJWtYAoKQaDp+u4XShxgXhYcbHoxNTllCwETGQ8ag2jmDVsk8w/wCOp/C/hn+mWV/utpePH+D5wmF39NY6UakjUYR1Dn0YgRM5zQAAAMdfAA4AOAOArjkMNQ3vgm7UKtBR+m9QHFD5tpnDtpy+t2R20gK/OsmFtuDpaL5mVyiT5qdEVAvZci5ch5VoSGKbwlWTBr0RPoZT07av9lHfrXo6yLApWMugKpPM9SV1cDm65s/wkOHZBojoqiM+6GpMSj4FhtayNAUi5H3LfQBG2KWssFoSPuJdKyMLKtpuLi+e3jwFICUg7CSHsNVlYlKdizOTvKdq3KTsG8pQirsAG6vAB5FdhP490U4gfjxi+DedoqO4YftmKdKNulO26jiOv+2Ga/bftVNFXpHtVHrpLpRFJTpP3z77T469++fTx48e4LueE+NY6UKk7UniLP8A7rNf3X6//9k=</binary><binary id="image1" content-type="image/jpeg">/9j/4AAQSkZJRgABAQEAeAB4AAD/2wBDAAYEBQYFBAYGBQYHBwYIChAKCgkJChQODwwQFxQYGBcUFhYaHSUfGhsjHBYWICwgIyYnKSopGR8tMC0oMCUoKSj/2wBDAQcHBwoIChMKChMoGhYaKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCgoKCj/wAARCAD6APoDAREAAhEBAxEB/8QAHAAAAAcBAQAAAAAAAAAAAAAAAQIDBAUGBwAI/8QAPhAAAgEDAwIEBAQFAgUFAAMAAQIDAAQRBRIhBjETIkFRB2FxgRQykaEjQlKxwRXwFjNictEIJEPh8SZTgv/EABcBAQEBAQAAAAAAAAAAAAAAAAABAgT/xAAbEQEBAQEAAwEAAAAAAAAAAAAAARECEiExQf/aAAwDAQACEQMRAD8A2t0YoQpwT2qVzMV+N3UHgrDY2eoM0y58VEbgfp9K1yMRmnuJ5h40jyYHGSeKrWE8u2QAApOMdqGCsmT8h70TAJwMAZx249aKBy4c9vTNUC0zDCgmmmG7Ockjkj1PrUTAjcy5XP0ouCgHae4IomOJHhgIc55PHY0Uk5IXLMcUBQ27n96JYO2MYLebHtRBA7BcMx29sdxQJqwZRtIP+BQKpjHHc+xzigNGoAO/k+nPAoAYlee5oBiGeWySO9AJCgY5PHagFCADzj2GaA2N2TkjA/U0HMwbPPeiyBLDfkkj04FCl1cBMgn6URwYFGySR6D2oAeQDAxnHGKAhU4IbGc+tFwnwDj9aK7f8v2oNu+IHxNvJdXmt9EmKWSqArA/mPvxUxMZNe3Ml1dvNcMzSSEsxPOferJhht/OWyAPc0UfdgDcuM8n50AMCykZFARsngcY/egTcbjnJz9O9AB2kZGSQOcUCX8x83bntQCMruJ4B7D1oCyOGzxtJ9M80CAdg5UjFE0aFJrghLeNpHY4IRdx/QUNWCw6D6q1EZttEvirHAZ4ig/U4qw1b9H+CHVN3Mq6hJaWMJ5ZjJ4hA/7R3P3q3ET+pf8Ap/lWNm03XkkkA8qTW+3PHupP9qxopV78G+s7VSV0+OcAn/kzqSfscVvIKzqPTWu6XKE1LSL+Bhz5oDg/cd6lEZzGwLrtPqrA8frUCJfcw9gfegUjZsEAffNADyHt78UAjCjzDJxRcO5Pw3gwCGOVJQp8ZncMGOeNoxwMY96GCbQffFFcUXKjDDt2NEo+N3yyM5z3okKuqJgIzONoJyuMGi4QfGcqSfXBoYHJx659qKIRnnsfUGgJn/poJYoTIGLY+eDzQFlQK2G/KCTmgbspfO0qce/agPGcR7nHf9vnQFfBPlOc88Gg7uucc/M0Bd208YJJweKAYrea4kKQICRGW5IUYUZJ570DYqcknt3FE0VuVyDzj1oamOlulda6puvC0a0eZVIWSbtGn1Y1NNbX0x8ENH0qL8X1NdtqDoNxiQbIh8u+WpqL70Tc6fcxypouiRadbW8hhLFFXcB7Edz+tNFvEZxkmmgShbA9PlUA+Hgg/wBqDgmBkd6ArJuJBGR7VdEdqWgaVqMfh6hp9pcLj/5Ig2KaKJrvwW6S1EFoLaWwmPIe2fAz81ORTRm3UfwI1mzBbRL+K/ReyS/w3x/b+1Wexmev9O6xoE2zWdOubUDszr5T9G7H9auCJj2n3PPrUXTlGBB2kYx96GlQMjJJHuRRXBgDgk8DtRKH8w4OfYA0SUlIMsFXJ4oujHH8ufnRRGOSNoJNAeFC77F2jPucfvQFEqgY3nj/AKaCUY58wwq54AoCzOmVMke9QeRnGR7ZoEIF7pnaTk49KDpSSwQntQJsGKjgggZ9uDQc4OOe1Am2UCkHOR7dqA8t/cSW8MEkrGGEsUTPCk4zj9KJT3pzQtS6m1aPT9Jh8SVxlmJwqL/UfYURuuhfArR7f8NLrF1cXciKDJCrbI2b7c4+9NGtaRptrpdqltYW0VtAn5Y41wBUodvGjqUdQyn0YZqAIreOBFSFFRF7BQAKA1xcRwKplcJuOBn1NAR7y2ikWMzoZnGVQHJNAuQcD3oBKkD2FBy8jnvQFxnjjmg4rxwKBMqCBtPNA3vbCC+tngvYo54HGGSRQQR9DV0Y91n8DNOvFkuOmZmsrk5PgSNuiY98D1X+1XRhWu6DqWgX72er2j2069t/ZvmD2IoGG7jbnj1FFlB224PB+VClN4DYJHyAojmPGCck8cetCAxgjPp6UaAGKtx6+9ATAXO7nFBw8HHLN+goJhBuj2FeAcnmgNazW8U0vjweODGyqpYrsYjytx3x3oGa5LEEjH9XvQGlgmjjMmQq4HBPfPYgevagG5nhe3tkFuInQHxJQTmQntn0wKBKTlAeDx60DSY+U9zn+mgsnQvROr9Y3W2xi8KxV8SXUnCrjvj1Y/IUR6c6A6H03o6wMVgrSXMoBmuX/NIf8Djt/eiLfjJwO9ZBiOfmKDhktzQAzYBLZ8oyaDF+rOptVv8AUjNZL4tjA/lT+kr3wvqTQX/pi3Y+DqFxKXurmFWAaPaVzg4I/b0oHlxqV7penRTXFu93dPLsESYB2k8n7CgnradLq1WaIOFI/K42sPkRQCg3Kcd6Dgp3d6AdrGg5VxnjmgKWB8uQGxnFAUgKuSefSghuqNC0jXbAWGtxQyJKdsYc4YMf6T6GtDzR8S/hnqfSUz3NvuvNILYSZR5o+ezj/Pb6UGfLzyD/AJoFFySQVBHpQDJ5kGByPahAbWxn5+po0OF3D+XPtQJsNwOe+aAuygmMkebgHnHFALHYpJwSeGz2oGpOJWAI49BQEZlYAHkg4oARVOMvtBIJJ7AUAX6xxSOsUgmjViFcKRuHviiVfvhT8NZuqpk1LVFeHRkPlHZpznsP+n50qPS+mWVppdnFa2cEcFtGu1I41ChR8qyHVxK8cLPDD4kgGVQHBNAa0maaBJGTYzDJXOcUCy5JOaA2OMfoaArkheM7vlQNYNOtoWLJCgLHJwo5NApPKLaNpGRQB6j2oGmnRvcyNd3O/DkeErLhkWgklIdCyZOCRzxzQEeRxhdpUnncBkD5UCxXjJ7+tAlctMsIMLohz5mcZAH09aBQYdQwyAeaAuA7MAQxHH0oG1481nbGVInuWU5Kr+bHrgepoKB1u+o6jqlvBH05NevEBPBK0pQR4I4BHZj+1Bb9IS7lsFtNWtYwDGFYB/EXHqpJ7/WtQYx8VfhGbdZtV6Uh8gy81mpyR6koPb5UGKY4YkeYd88fbFAI5AC98c5oQBb+U9+9GnN5RgDgjOPWgAN3yMfWgAqc91/UUD2RSSRg9+49KCR6e0WfX9WS0icRwgb55WOFijH5nP0FBYNRi6dSR7HRNPmu0hOW1GaXaZMdwBwAP3oynE0XRYrFtV02wS4ECj8dp1wcsE7eJEf39qlFZ616ZttPu7Kbp9Zbi0vYzNCcgjHqoHuKsEp8LPh7P1PqjXerxywaXaviRSu1pWH8g+XuflQemIIY7S3SK3hVIo12pGoAAA7AClEL1N1RH0/oTalcwx+IACLaSQKx59Ppmshv0D1jH1ZbTubU27xkkAnKsuSMg/UUFluLlLaJXETyecKAg554zigXiubeRnSKeJ5FOGVXBIPsaBLULoWkIfw3kYsAqIOSTQJMbpm3oqlmwACeF9yfn+1A+Bx34oE5IY5P+YFbnPIzQKAckHuRQCAQOO1AL8r9KDhkZOT9M8UCcrxgAyYJzwD70CT3Itxm8kgi3fly+P7/AOKA9pskhEkZysnOfeg6RH8w3tgjAHtQRZ1uystSg0m5eRJ2UbHceV8fP3oJkBSAVII9xQFdSRwKDDvjN8L/AMSJte6chxcgFrm1QcSf9aj39x61YMH8Q+CkfhqpQncxBDH5H6VRwXJ/Ke1Am2QchuMYOaNFSAVznB9qAm8f10D2RmX8jDHP3oLbebtA6ej0m2LrfX6LcX7IMskf8kf6HcffIoG8yTadZxSTxCK3kRZUwSFfkruIJ78GhiS6Y1OS3160uZJFWO5bwZtxzuQ8bcfPNMZXvo2wsLnQ9R0q/maJNNv5Yo3bjCuMAHPzqA2jdUan0lF0/ZXcElxp9zE+5WVd/DE71IPPB7H2po1bSNXsdYthLp1ykyEcj+ZT817ioITrnoux6vs1gv5JYnjz4ckZ/Ln5etA+6N0BemdBttMina4WEFfFdQpIJJ7D60E5I4Vo9qnnsQO1A3k0yzeTxhCizZJ3qNpz9RQO449igMSxHGW5NAIwBtUAUAMORkfegMhG3jtQD8+fvQGXJz7UAHuRQA5YDI5FB0qCQA5yaCs2/SFit/Jd3AmvJ2bO64ctt5zwD2oLMilVAUDgcAelAJLbhgZz3oGN9HPIYmhtrWRw2czjt7Y+dA+h3mJS67W9gc0AvuLYANADpkZABHY85oPOnxy+Hx06Z+odGjC2jt/7qBRwjH+cY9D6/OrKMebcceHwfaqCYIyDgZ96GhHOFJI4/WjQpXnsaCz9J6fDqGvRC8OLO3Vri5PB/hqMkfc4H3oDT3UupapcXrKS9zISgDdhnAGPbsKC5aLLBHq9p01c6bbagPE23kpJYhmz5IySAAMj6nNGdRnT2lu3V9vaQQrJDHfCMFj5kAfufsMUFogu5H0jrLUYXK+Lq0aRse/lf/8AOKlFfudagvbnQpNQRmtILydCwPdCQcgMOMZFQanPoeiawBd9M6s9jeKPK1vKQp+RFA4septa6fuFtuqbRrmzx5b+BAdo927A+vsflQXfTr2z1O3W5025juIW/mjOR9KAZI914khaRNo4XdwT9KAl3b2+oWpjMoZWbOVfnI9sUCrXUNssUU8w3sQoJH5jQLvwQQC3NAKvuUPtK54waDg23v6UA7weBnNAIOBigMr+hoOjdZQdhBx3waAVG0Z7UBWfAOQSflQChyNxBAxQRutarb6bHALi9trSW4kEcJnGd7ewFA/j8QEK/IA/MBjmgWDDBB7igj9dupLTTbiaHZ4oQ7A7bQW9ATVgwXSNV6onl8azW6t45pWdxHIxWA/zNtz7A8Glg2S1u7fX+nt0J/H2c4MMhmQoW9GBUjj60g8sfEHpebpDqi4sHLG2Y77eQ486E8fcdvtVFekGW4UfegKVAAKgnFGhuDzxQXbpDTZF6a13UnUqrCOzQ5wGZmXIJ+lE0ppkEK6nJcRWcTW9hA08iKcjcowpye/mxQ0+6VRbC/jvLm48L8LG9y8pIOXxkDnuSTipqHXQMng3es9S3fhn8DbvcZI5Mr/lH700dc3Dad8NtPs4nU6jeXD6nMCwBRF5XOfU8YHrTNJFF1X8RawW1jc4GxTKNrZB385yPkBTFw1stSu7Ni9tPLGSQfK5Aphi8J8UNUm6fn0u72yvJ5fGbuF/39aYYtGgadp9/axXnRetzaXqnhqZI3bEcj4547Ak/X6UxFisPiXe6NMdO65057eQAr+LhUlHHbOPX07UwWXpQ6BqMo1LpgW0sioVI8Qgxk+684qC028M5890Y3kHKbUwF+lA4LDOzu2M4FAOG3DaoI9cntQdJxzQEyR259f/AKoGl5fSQRFo7ZpB/MhYIR9zxQdayyXKb7gqox5Yo2yB9WHc0DPUIWnhWKxkuYFRs5gcKWbPY59KBkx6isVeSGW31JNwHhyOUkA+o8v9qCfjkMo/LJFKqBmRvSgc2swnRyFcYODuXGfpQMtRsLK8vYJL+wjuGiUtHK6hghz6Z7H6UEmCsig84I9RigiruC9t0DaaVmIIHhTOQMeuGwT9qCJ1ywv9T0U29xFFiaVBJGHz5M5ODgYPY/arKJPTtLW1t44i7SKq48w8x+ZPrTRJoipGFQAAdgKgzX47dMJrXSrXkUe6807MykDkp/MP8/aro80FQyZ+tUJ7hvH0x270XQ7KGtXvIk0T4c9P2bIhkvpnvJVfjIxhf7qftRDXpu0/1DpzXltUlkvmWMBI+2zdnn64oYa6yX0XTm0i4jQ3t6wmuV53xov5UPpyeeKyLbpFtZ6Xpmn6TqNq7/ic6pqQRR/DVf8Alq2fTOP0FXBnXU+ox32o3lzeW+JrxlMXHKR9wfbJ/tVWK5f3AnaAjafCTwwcY4BOM/qKKSjA4Dg8j37UHZKkE5P0olSFlcLDdJPbTNBOigjxOVZu3+80Rbbnrq9l0t9I6isRd2rgKpPlZMdyre9An07oupoh1zo2+lea2fMlr+WZFx7ZwwqWDVug/ihDq7R6b1EPwmpMNokPlVj8xng1BqEUe1EAJOMDOc5oDSxq6YYeuaAJF4oCBUQ7mJ45zQHYB14wR86AVjBXyjge1AEcRTHlA9hQE8kbgEohJ5yQM0ETHNqMOr3IZQ9tIMQyEjKt7D3FBLqywRPJKTuxlj3zQI3Ut14e+yhWRj28Q7RjH60EfpF3rU/jLqFrHbS4/hqpJXH19aCRa8jgiVr1xGwXzYyf99qA9tc29/aRXFnKs1vINyOO2KByoxwe9AYocHGKBvdwLcWzxSLuR1KuD6gjBoPHXWujt071Nf6YSSkUnkJ4yp5H7f2rQgWAA3Y+1An4j/1t+tBrHxKuYS+gx24LRx6ZFtI/lz60FY0+/v8ASphNpd68EpXY5AGNvzFF1YOirZbzVrvX9dkNxZWH8eeaY5Lyj8qj7kcVlETqOqXd/HrPUNzcNE16Tbwxf1JkEgD2AA/etBte9R2Oq2cv+p6XHJfBFjgmjkMaRgAAEqO5o1FWfbgjsR8+9AlI5CgEggeoNAq0iug8uD7g80KKmCcZ7fPmjJzJfT/hWtjJvhOPK/OOe49u9A96X1W90/VrRtNkkSfxQF8I5yScdvX6UGidSLpfVFzcvbRiy6kgZBGysFW7B9T7HHNSjU+o9S1iz0e2uNLmX8RYxJ+KgYeVwVGTn5d6gjug/iU3UOt/6TewQpP59skL5B29x/8AYoNHPB78Ggb2l3bXO78PKsoyVyvIBHBFAoSkbfyhn4GfWgTnmWFN7ybAvc4Jz9hQRdx1dp0S3Dw+JJHbDdPIUZUjX3yRz9Bmrgzbqb4x9Oxho4bB751O5HPkXPsc80wQHT/xrJ1IHUbGKO0kdRiBiAgz+YjnsPpTKN/tLy3vLOK5t5klt5F3LKhyCPemAYLuK5XMDEj1OCP71ArGWLMPT0oIbU7h11u2t49OllWWNm/FIRsjI4AI/egfQ2ktpbww2XgxoDl9wJ49cUCHUGv2GixM13Mkcm0squwUH5/SrgxDW/jFcXOteHb3otrKEEiRISRM3zGc49v1qDT+gfiBpvV7y2unxTxywRhz4ozuHbOR2+9Bmf8A6kNIEWpaZqiooEqtBIR6kHI/atfRjDEt3AKjgVQjug9j+lQWh72e/htTOzyeCnhHPomeMYoJvQum7vVD47K9jpsQBkvZ5NoAHcgUAa7rKamE0Lp9Xh0G1OZZTwZSO8jn9cCsivdS38F9cJDZIY7G2URxKe5x/MT7nNaEKrENwAFPPlosFwS2cd/cc0UlIm3JOeKDo2LH+UA0SjgDk98URzPiJ2449e/NAbS7v8PdpKkpikQ5WQLkqccGgmYNQmXWLeQLG9wVRQVPlcj+Yn3xQa98OviAjz3WjdXSpFdliEuJCNjDtsJ7enepRdel+kdL0rqOTVdIsoYklV1dixO3nunpg9jUCnU3WMeka5b2EUcl3JInmigQs6ZPlJAHY8+vpQP9O1m3nthNo0cTwM2JDwoVj6H5gd6CbhtUiVn8TcXO4ktkZ+We1BAf8Z6fZ2uqXWpyxQrbStGseQzMB2IA961B59+IHXmodXal+HsPFh04HbHCo25+bY/zQWv4f/CCxvII73qC8iuXYb1tYZeF9txHf6U3BatX+DvSl86x6cr2dwjbnEUmcj6Enj6U8hLdJdEX/SmowJp2tTT6Oc+La3HO0442+3NBf1LmRUjjQAfmc+nyHvWQockYyQcY3CgaabaPZxGNnaUFi3mPb6f+KA2q3RstNurnBxDE0mPfCk1YPMemaP1L8RtYN9fJPc2aMUaVmCKg54H0z6VRYendf6Z6T1W56a6j6fgfwJyguhGJmPzbIzjHtSjTn0zSunbi01fSkt9Os5GAmWNCDOGxtXb6HnNZEZ8etOF90DPKFy1rKk3zAzg/3rXI8u7zvOTg4zVoTLDJ81QWDTb2SwuvFgcrkbXwM5H0PFGqsjpd6+kcT61Nc2ieb8OikFc/9PA+WfSjKA1nWBzpFlZ/hLWM4KH8zsPVj6mghN4IyQRk5NGo5BkFmyAfSgVjChdpGO/FAXYpOHLBe/FAQqoBJbA9sUBGxgtgEj/eaCf6DGjt1TZf8RNGumKS7mQZQkDIB+WaMrf8Ub/ovV7V20JIYL62K4khhCLOCcEcAdu9BmCuEQvxvyFUg42+v+/rQaj0zax/EXRY9Nns0t9TtM+BqCKAjEclXA98jn+1Si7Cz6u6O0tLjTrxLu2tQJJrDwcKE/m2M2SfeoLrpupDV9Mh1OytUS2vIN8m4BZQf6T7+vPpj50GfdK9L6rJqk1y1y0elRDKRqdjHHoyDhjx39e9BZr7fagW0j3kul3iETRqHkeF8ZBUjkZIxjtk5rQ86dW6r+O1OcW0UtvaRsY4oWfLKBxz7k/5NA46P6X1rqS6WPS7V9v88rAqi/f3oN46X6C1DSotkus+BIwKl8hn2+3PapROXPT2t20bPY6kJ5UGYmbIfIHGW5z68VBI6DrzzWSrrAjtrwFUbDja5OBlfuaCbluJLeNwIpLiVF3bVXAP0Pv8qBxLO8cYcW7vnuqkAigNFKs8CyxlwG/lcYI+1A31ayF/pt1auSFmiaM/LIxVgwfoO413o3qqfSLyUSwodogAyZVGcbPTPr71aNDvendJ6wtbu7Fi1lezK0bS4VZMjtnFZE0bC5u9Jh0qRAr2yw4uWx59vBI44PegN1tpbap0lqOk2sipLPB4aFsnHbBNOR5A1exFhqFxbeKkngyMhdOxIPcVuhiZFz/zBUEwcKvYnP6fWi0+6chjn6h062uATFLcRrIMnzAsO9EehNR+GvTV3GUh0+O2YsGaWHIf9amjIfib0no3S0VtFY3M000zMzLJtLKvvkenyx96oz0rwNjA8cj2osFLbVAbOc9jRQiXOAwxnj3oBlAxwDj37UDY+vHOQeTQBIdqjcPMfnQwJclWyBgCjJBFeefw4VaVycBUGST2wAKD0L8H9C1rSIILjWLSCytY1lZASVnlL4PI/wD8+vvUo1uwbxI5GkjdVc7isvOBjtj2qBWKFZiQ8CJCB5FHYj5jHFArDbQ20ey3RY1HOAOPsKCH1u61CPSLt9MtlXUHUrbCbJBbPdtvYetXR5T1y2udD6lni1ErJdJLvlK4wWOCePvVgsV/8Sr67UW1vA0NiowIonMe4+7FeT9ARQRmodWa9EYpPBhs1Tygw26rk9xknkn70EjonxZ17TXjAeKTkZ3L+YZ7N8vpSjX+lOpNM6umgkMG3EgBV1DYbG4kewz2NZGkC43CP8MPFBONysMAD50DaHVH8S6N1a+BaxMUjd280pA5wPb296DrXWLK9WNoJdtwybxDKPDcAnHIoJBifTBzzmgaz2UFzPFNNbwvLCcxuyglT7igdRRKg8qAZ5JAAzQEnuYoHiSWQIZW2ID/ADH2H6UERr12BY6hueIQJaO7SK/nHfnHtx3pyPGWoN4jynuCfU963RF+DL/UtQWTkjaWY/8ATnHFGql+j1VerdJY8r+KiJz/ANwoy9C/EjqSbpbRY723RJC8ojIcZ4IJ/wAVkecer9en1+9FzeLCCq4URjgDP7mtLhteadBY2kMczyHUpcO0YxtiUjgH/q9celAiLy1kjCX1ruyMLNGdrj0+h+lE0+t+kNQltJ7yKS3jgiTxUFw/hySp7qp70NV6YEBgWUNjBoaKeAODnHrRoVgDnBP0ozpxZ2f4y5trVeGuJFiBPpk4zQep9C0LTembS30fQbWP8ZsDyTugZgf6ix9fYZpbgmbXSmXULaa6kMzpltzcjJ//AGpaLCY1CDsF74PrUCgHY0HbSx7Z96BGUfxB2xjtQZ11t0Tb6jNfyw2wM18gV5AcBdpzyPnV0Yp1F0o/TEczXjXaTOQYpIk3QlT3B9Rj0zVl0VKbVppImheUSwbsgFfXHc0De0tri/ujFYQSSyfmKopPHqaDV/g9p+padr/gkSRTzKu0kZRlPLYPbOPf2pg9GWzRCMJAFxH5do4wayKX1z/G0CdzqLWRkiaTxQBLudclQvovbv3oMU/4Z67uwnUAt3u1Zw42yhmx3/Ln8v0oN86L1d00i3i1UiGQIocNnEbnkqT2xgiguEbI4DIysp7EHNAZnxQQ/Usksej3EsCl5EUthR5sY52/Mjigr6Qrp3R15LqEcIlmgdpFGAsY2navPJApyPJtwd8rnGBuJz6Gt0MzGSTyf0qCwSKA5ZsAjnn2otTXQYj/AOMNIDqCrXUZwf8AuGDRG6fF6Gyfo6+ub0CR4EPgIScLIeAcfc1keatN0661a+S3sYTPKzAbV9B7/StLrQ/iXp9pYLp8elWsUM11AzXMqt53I7g7j244oiB6W6Tn6j2TeAy2FspTeB+Z+/8AmgtnWlvpdl1Dp1pq07Ja20GFQpuDHHAwPf39KDHriVTKSPOCeBnHHtQGsrG5v5pfwcTOIlMjgEeVfck0XRIreS7uUigRpJXOEVe5PtRE/wBJ9HaxqvUcdhNFJp0lviaSWVcMgzxgdySeBipo9T6O8NppUJ1K4iW5KgSvIyqxb5jPH0paJm1NvKivE6Mp7MpyP1FQLRTwy58F0cjuAckfagOTtO3+Y8igMWCIWbOPlzQNhNBOWEbq5Q+YKc4+tAD7JEZgQfXj0oI/VtIttXsZLW5hRopByCP/ADVlGRa78Erae63aXK1tG3LAncM/Kmh10l8IZdBv4rxtTE0yggJsyoz6/P0po0zSNKEMdo9xGnjxuzkqMAEgjj7GmialjWQMgyCRyQcGoITqHT7q/a30+G2jFmwLSzl8GPBGFA9c5NBPRwJDbpHCipEi4CjtigqfWltqCaG8WhNbxyzOBIs8W8FcY4+dWQQ/wtuZdIGqadrknhy2u2QyOSEZOeRngY+XvTBZZevOmhC8janbqiZ53Zzj2FMFcs+sh1ZqsFrp8UkGkrlpbh+DNzhVX5Z5NQTfXyWUXSV2t+wW3EZ5I4HHt61eYPI0mA5C9snFaoLsPv8AvUEk5JcA8cZG480WnOlXX4PVLO4yQ0cyP244Yf8AiiPUfUump1B0/c2O8xfi4v8AmL3UcGpgw/SujNX0Trj8PpckimOMvHO/kEg9Rjs3PpV0aFq/Qqa1ZJ/qcrverEqNOwGM+uMfemiVtrKbQdMNjp9rvtkhPht6mU5yT8u1BkvXg1qXUtOvddgRY1R3j2YHiMvZSD27CgzSCyuNQ1KK0giL3Mz4VAOc/wDignoNNOnaHeiW8hgkku/Al2+Ziqgn09M0ETp0qpqSmGKOdFcEeLwMfPHag3JLuCRtPmQWsDhNphtVAcn1w3BPFSwDdWGpX1/OYdOtbbSrlQ80szHdn0GR24/c1AbWemdatLbTJdGvJIJypDQwMV3exwOPatSz9Ei/R+txy2mr3evyHV4miWIDhGwwyGA7nGRS2YNZAUBWYDdjGayEvxMYB3nYu4KCfU+woG93c2enWs1xcPFDCp8zEgDPzq4GGgz22saS1zZSZhkdsFePXt86YHWmySeLNDMYikZ4YNlvvUD+VARxQJqgwRQHUAAe2O1AWOFRM8mDlgB37fagb6reXFt4ItLZJnZsuWfaI0Hdjwcn2FAz0nWX1i4u4xY3VpFbv4eZ1x4vGdy/KgkriN2aMRlQoOW3DOR/5qwYr1P1tp2pdS3WnanKkGh24kRl2eaYgcb/AFxnnAqiv9Jno0dRLJPbtdQtkNPIALaMnODsPPpSjbdK0DTbWQXui+Gsco3BU5hPP5gPT7VkU74t6PZHpq/1N5ZZbwrtRnmOwDPOFJwPsK1xR5ybudw788VaC5X2WoJRULSBpAe5PA/aiinAZnHck4A70THq/Qr23/4Y0u4lmCpLBGA7epxjH60Du+WGOBvFlFuWOFcYyCfbPrUojri6k06xX8PFNfBUJ3ltzM3scVBjfVvVXVNit5dapNDZGQGK3shjeAe7YHIwAOT3zVggNTiu+orrR4p7m+upJFR7h3TPhggDaoBwRjnPH5hV0af0xotnoD3l5dWdrY2YjGLhwPEHoef996CC6m0HpuPpk3Wny2s9sJPHJ3AeI2D39T37UGU9QTDULuGPSLPwIyoVIYk2lj6/X70G2/DPp0hVudRuBLcwxhRGkeEjB9M+p96DSLprVHiieaAE+YxHkke4H1qUOIBawL4uAuc8nvj71AwjRtQ1eO78QNp9odyLju/qT8uf70Gb6r8SpLzryy0vp+4NxYSSCEswI2u2Rn3OOD9qC4dVamen9NlaC7tUaIFvCmnHiy4HJXJxnOeDVwed+rOvLnqSyWO4jZSru/kc7ck+30GKosXw2+KmqaDJDY3jR3OmqNoRhtZAP6SP7Ggtmt63qbTJ1XLazJpslwBFblypEOAA7L2OWANS+xrnR2vW3UmjJeWp8wJSRf6WHeoJdSPMCRmgMq8DmgBpNsgUIxBGSccD70DczmS8MDWoe28MN4+f588rj980CktuJZYpFdlKZ4B4OfegQ1hpIrVjbsRMBhBj8x9qsHnX/hm36y1O/u9V1ddPmS6aD8OkQdyxOSe4OMmqLUvwQsYY4Xjv7m4YEEhwFyMY7fXB5pRbvhp0jqfSMV7b6jqZvLGQAwxAEBDk54PuD6VkVb49a5DBpiaNaeF/FIaQDumOwpzMGDEZQZ5+VboR8In1I+9QWDY6gFn7jjHpQhtJEFbAGBnijT0P8H7qPVOh47a42yNaymPBOcDupoykep+m73V7g/8Av2itQowvJIx6j5/OpRjfUWrax051RPY6LqFy8YACkebO4Z7HjNWCY0ToW2utJbqPreW5na4O4R78cehY9+fQVKLX05p1ro97awC4kX8VFmJLeEKdoyfOxJPbHbHYVAz0rqKPWNauri9t1ktJgILYgEiNFJ/Op9STmrBBdeaFCo0y3jt444DI3jLE204Y5DD+9UPPhv0NaRtPq99mSLOy22nOfdh75oNC0vT7m1uJGvGiii3AW8UDbQAeDu9zUohLlhouqap1VciF4I1FtbxSthtobBIPuTn7VBJ2vUth1TYk2ULi9iALwyKQYz6Z9CM0Ft060/DWEcDHe2Mucdye9BFW3SekWt3LPb2cUTsd2UGCG9x7VYMzufhzdX/WmoXj+BPpx3I7XZMmXYckc8EVRKaP8I+nXikLQuxOQSTnBzj6UEjonw90XSrq3S3s7dplJcl1EhGDx396lFx1TQ4NVjaC7UNCU2lAO/8AvNWDCLp9X+E/WgWImXSp2LRq7eSRT3B9iP8AFSjd9P1+21TRodVsMS2rLmTbyUGOePXFQSltcLcW0c1vh4mXcjDswoDLdRm4FvISsgXeTghDzjAPbPyzmgVFxCzuiOC0WN3sM+5oDqySJmNg3rx7UFb60tNUubGJdFdEvhIdryflUFSM49TVgyTQenJemOorf/U4H1Fpp1edAh/hOQTuQ9375JA4q0bnbPBcxxT20wkjKkqYzlT9ayGWu38um2MbLEJ7iRtoUds+/wAgBzQeW/iHqi6j1PdzeL44HkL9txHtWhVUOVyvHNB2F9zQT8hUAhAdp5FCG0mSAzE4HGDRppvwL1bwOpJbEsFiuYyVX3deR98Zoy2ZtRgmjkSRZocEp51K7se3vUow/rfpFE124mVpfD4mk2MWdCc4A+VWCH1281/UmFnpklzPYRFBEG8uGC4yQfcn9alGgaJo95rRsbi53WaxwrHOm7BjYcHnvz/moJaw07pXSI5IW1K0CQnDhpAWB9R796CudY62msTRW+gadI8KnDXMkLLv9MA8HGOKC3dAXF1dRfh75f41moi4G0AdwcfTj7UFhv7RjqMBV5AJFZHkR8FRjIx6CgpXVNjJ1JqNn07p26CztSJLlpIydyj2J+fGaC+afplrazqLa3SKNIggx3IHYUEsBk4wQc4oK11L1z070/M9rql6wuVA3QopLcjNBDwfFboqeSO2W7kQNxuaEhQfnQLt8TuireVoV1UeXnckTFT9DigHRuv+mbu9ZV1W3Nyc4IRlVl9O47/KgtU+s6baw+JcX1umRkAuM/p3oK/1t0rYdX6cqXKESqN8Ug/Mp9P1qwZ702mo9GdUTWJsmOn3EY8CAORGXJAwScjJ5q0bJDNLb6YklxbKsgA3wwndg9sDtWQN3aw3ZKTwLLEQOGORn6ehoG1vYAw3FikRt7JSuH3Hc/GSc5P0oHn4aO2uGuYyiose044wBQIm6F1dwfh5ARs8R8L2BHGfnQHv9PS4PjxrGLtFKxysm4qD3oCxboIIo7e1jhQHzAYUJ8wP8VYM56j1ktaal1BMrS2sAaK1OQDD6eUepY9yfQVR5zv7hrmaSaRtzyHJY0DcE4BPIPb5UBwOO4oJYzFvzEYHAH9XvQhNZN7AEgDOSDRo/wBA1SXRdVtNQgb/AJUgfBHcZ/8AGaGPVlhPbarZ2t5CEeORBKje2RUrI1zYxTBhMinIwcjvUEcugWkO4AMisMEA8N69u3yoERrOhWNxNYy6hapcxAeJHM+D8u9ASLStLlm/EWdpZyxy+Z3RQ3I5B44oJKTT4blFWSNBEOeBg5+goFYbOK1TKhIxnIbGMH50Cpcyo6AMrIcM2OD68Ggb6Lbbllu5Cd88hYBu6rztWglSNkfm4P70Gaat8Rba96w0vp3R2mhufxyi4kO3YyDOV9+f8VYMw+P0cP8Ax4JVuEKzW8bEr5tuMj0+lUZ7Y2X4288GK+towRlZXYqv9uKCQi6YmbT2u11GzaJWKnYxbBB49KCFnhubdiwL+U8OhP60ElpXUFxY6nDdXQF0qYbZKxwT9vWg3npb42aHcmC11C3uLSQjEkpIdQfr3xUondP6x6e6tv7e101hczRzrNtaFiFC/wAxPYHtUF+lj8bYCTgMG59cUC4OBQQOo2eoXepFTeL/AKYQN1sEwWx6Fu+DQLX2kw3Ok3Vjas9qJ48Exd1PHb9KCE6R0G86Ut7mK71KK4gklM7TyKRIBjtjtjj96AOreudJsrMJbXksk8jBCbVdzRjONxBHP/3QQ9x1jcWGkERWWqXdpMPCt7x4wfFOOWPbA+fAqwZr8TJ9Qbp2ymvEjsrSTEVvawyHz45Lv6E4wPqaoyl8g91OKDlYEc8mgKW5PH7UE80f8PPHl7gDFAZkUjawUIQG8w5ouknAUbl9Dg59KK1X4Z9XXFvo8mlRXax3KHfBG8Rk3qe6jHOc54+dMZO7jr/qK8vWtba4tYu38TwvDOMc8N60wPLbrW10PS7pnvrnUtbAKobgBUUk9jg8f/lMC2rydMdRSaRqWoLEbx4UefwxkL2BVvvn9Klgv3Tp0lPxFno6wJ4IVmEOMEHsf2xUD2e4ks7n+NGDaCMu8q8lCMcEfPNA6tW/EwrMybEYZUHnI9Cf/FAzu7G4LXTWs38SRNqhs4Bz3z9KCO6x07UNT6altNMvEs7xkC7nPlI9R2/egwbrDT+r+kupLCeK9nu3KBYGRy+QvdWFWCU6avtA6h1iKDqLRhpmpvkxz2p8JGb3z7k557VRX77TdHteuPBut401CAouyXGcdvmASaC069030brYaay/CwPFwWspRErfUN7UGZX2hWSiY6ZrMc0CvhUlBUk/UcGgiLq2mtG8F54yDwfDfIoGkrRsSZXwOB2zmgsvw06XHVfUcFvI22xQ753Ze4H8v3OBUo9a6XodjpltHbabDHZIhVsQqBuA9DxznFQTQUe5oDYGMnn7UEbpV3JqDyz+BJFbBtsXiDBf/qx6CgDXL42cSRwGM3UzBQrHGFzy32oG2i2kKTSI80lzMow0rqQoyew+3tQO59KtJJRI9rEzgg7igz3z/egZ6paJdGGwW4eBXy7pGeXUdwT6A5qwebPjJrcOr9TvbWZQ2Onr+Gi2nIJHcj7+vyqigOuRk+vtxQAqEk4BU0ABj7j96CzzKxYD0GeM0CQG3OMAjkfOgbSZwzE4PJyfWi6caTdzaffW95akrPFIrLg/tRHpGzs9C6t0W31FrO3Y43MrcbH9c/eloZ6v0JpWoKlrHHBbScSFEHYc5Pz71NDXUoJrK1g0dvw9qsspW3nXaN6KMrHnH5ieSfan0U3Rr1uidaRbiwk8BUSS6naQkjc3ZcHaRnn70wbja6lZX+nw3NvMksM+FXnPJ9DUCeoXj2hSG2t2km7op4U/f/FAvHaNePb3N0jRzRA7VD8Akc9u/FAvcxnawZQ3HYtjJoKfDFAdeub6Vo1dSULIBtTbgYOfU8jNWUVvrm5ih0m1urixhlsI5HJliOwR5/LkkHHJPamjHdQ0HWdemlutN0+YWBYtC0rHDhjwVz3zWgx1n4e9U6QE8XT5Zd//APR5se9XBXbjS9S0zAvbO5tyWKAOhG4/KpQ3ZHXO5JFK98qRUGhfCbph77Uvx91pv463wVjR0LR7s483796WjW7rTrXpHWrSW2YK7lmXTbaIFpCRjjHOOSeeBipaNLtXuIre3R43lnkGXYADZnnmoH6Dkbzn6UDGWe9a/hKG3jsW8riQMJS3svp86B6zgMQmDtGT8qDNb6XUpOoPx72tzOkjFYowOduDwDjj70Gg6Wsq2KNeAJKRuKk52fIn5DvVkENrvW+iaSAsl0txI2Asdud5Yk4A4pgzv4l9ST6JZSXbyyprWpw+FFa5G21gz5icfzH3pgwCSQlh688+tUEwjjngZ7UHAHuWAHpn+1AXj5frQWXOGBZcKSe3c/rQIyAtnI27eBj/ADQIMAuH8vHBB9DQwVpPLjOckEZ/ahi9/Czqj/S9VhtLm6aG1uZFUsT5VOfX5Gpg9GiNJArxsrxsv1BHypYGF7pljeG3kvLZSlqzNGGxhSRjP6GoG1yLUWiWc2nSPA4KJGItyYHYHHarop3wu0jWYNUvzriNBp8ErraRMANxJ/N7nA7ZqDUHgSQLvAbacjI7H3oOuIFuYzGS68jJRyp4+lA0m0yDwGjiTw3bzBwTuDe+TQVbV+mLmW1NtbSok9weZiC2zPLEZ+/FBM6Xo40/TYdL8Jr21G4vJcuCck55HbFWUKQ/h4tR/DTz2o8TK21qmMgKOf8AfpmrokljG1i5BHI57D5VNorut9Lab1LA638W6H8sboNrqQckq3pntV0RWsfD6K7SGC3vTFahQJY2iVmkI9d+Mimie0Hp2DQ7AQacio3JZgqjcT3zxk1KHGldPWtnqMupS5uNTmGGnk5KjGNqf0r8qgmkhVGcquGblm96BDUZZYLGVrdN8+MIvux7UGKTdXdbaRrFvbaxbWN4d58BmwCjHPORycLx2q4LNe9S9TdN6I13qkWmzSXdwBCGlO4hiMKAB2A9ag0WySQwpLLtMjDcQBhVz6CgoHxF17XbnUYunulgsUsu4TTvjIUAEhR+x4qwZwtkOi7651PXJobm4tohHbQhdgecjnaPZeOfeqMy1vWLvWNQlvb+ZpJpWyT2A9gB6Cgjy5AO4A5oAGRgBR39aA7Z8MkFtxPY0AbV9UGfpQWhj5TkBQGxuBoEGG1iQCyHvj1oELgSkK6oRnIBIxzRdJ28Q3+fHiAds96LoH3AF1wCfyijNbF8JviI1rbQ6Pq/iSopxFOx5Uf0n3qUbWQk8II2SRyDPuCDUHMpSIiJQSBwDwKAgTxApnEbyIQ+APyn0+9A5B3AgfmoEWgcb3VlMpGFYjt+negSs7zxH/C3RWO9UElM8SAHG5fl/agNdXcEbJAZ1WadvDQDJO7Gf7c0ED1dqWv2enzw6Rb24nZfJd3EwREHqxyMZHzOKBbT7H8PZWTK5uZ9o3Xm1SzEry5PsT7UFF+JnUezSZ9LttRs2km2m5KSFWXDZI491AyBzVwK6J8T7CRtPjee0tbaGAtdNISdoXgLEo5JJxyfSmC6aF1fo2vELZXDJOxwkMybHYe4HtUFiJWJd8rKqjuTQcZV8SNI0dy43BlGVA+ZoBniE0RU7tp77Tg5zQUv4hNrU2tdNWOhylPEnaS5UHGYlAzn5cn74oHGt6l0z07k6nJC123HhKPFlbPptGTj9q0Kx0XMvU+ty6vqQtpWlZo4LOdGDWsak8Aflycgk+v2qC8a1q8OnaXLPOz2kCIWkZ+CqjgYx6n0xTBkmp9Sabp0KdRyI5vJkaGw08MVKIDw8jA557896QY1q2o3eqXr3N7O8skjnlnzgn5e1UMCGV/MOM0BJFOVwfX0oFtgZTjkg8UBtpOeO1B3hg85FBZXVMM+VJAA2+h96BO4IMJ/p7qvuKBKacmOKB5CYYx5UzgDPfHzoGwD5OApJHAHrQEAk8NWdNpx+XdkA0AIGhkGWOQcgg8UGw/DP4kmwhi07WCTZqAiSbstGc4+pFKNvs5o7q2Sa3kWaJxkOp4NZDOHUh/qL2k8LW78eG7kbZv+0+/yoEZp7fUpX/BXpgvYZTCSRtO7vtwe/vQdY6jeyatPp91FEPw8aSNMoYbi2cADt6Z70DS60KW7luJdV1JniJzBtURG2b0KN7+/vQKSWUWnLLqN3cSLP4ex5Y8jxiPykr23+nzzigpXUPVOu6Vqmmf8UWttb9OXDqkjRnfI3H849uRkDOKC0axLFr+nLB0rrUMM0bqCIGGGX1AH09qsGc9UfBiTV9Vhu9Pu5oPGLNeG6bczN7jHvVEr058Gre3sLeDVrmOdo3LmSFNjEH+XdntQXO51XQOl5YrCKGWa8SMYS3tzMyLjjJHb9alDqz1S5ktJ7nVdLmSVDiOONfEMiE4Xy+h9xUDm11CaTxEOn3VmpHFxKFCr9s5GPmKAus6jb9M6RJf3c88yxpjcxL7uM5OO3HrQVTSupoOuYdZMTSpptriNFtXKXDA/Pjhs9h2xQOJ7Xpnpa2S91WK2swqjbGw3ysfcnuxrQsGmapYvpwvra1FtDL52Mi+Gx49sZoMb+LXV0t+jWl3OYLGTO2zjx4h2nyszHsG4/Sgxt5ZJmEsjl3PB3GgSlyXBxkDnNADseB2PsaA8SoXQyFgmQCV70B5R/EIjYmPJxnvigEKcYDfrQF2/X9aCwqC7l2zwfT/FAJJ5747E5oGTqZArKOfccftQHZWwmOD23Z4NAEkTEBmwR7g5AoG7KSSE5HyFAMTyQsMHa/cEcEc5oL58P+v7rppdryPNAXx+GfsQe7Z9D2/Wg3zSdX0fqzT08F433eYwscOpHt9PcVkQPW632mX9vfWdrbXiRgrIdu2eHIwGD57+nIoKdc/ELVdC0u5afp27SUtta5vJMMzk+UDjzYHtQWDpj4gxXmif/wAitXZkGZzFGW8MehZO+PmM0Fibr/poWQmF6xXA2xmFg59sKRk0C2nQP1KFvdb0vwIUJNtDKcsVP8zD0Jx2oJDTNA0vR5p7qzs44pJOXkUc/SgNfa/pNvbF5L2JgTsCo2WJzjGKA1jcNcxOF/m/I0zbt4+gxgenNA5s7CCxWWYQxpNLgyMiY3nt2oHajcuexAoEL1C1uyFkVHO1ixHb17/KgwT4rdXWep6oul2OpywaTYqVLxDyySDjaM9x6Z+tWDPdB1TW7Wa9sumpGlursqMQRlpXwd3BA4571RcdN0i41G7h/wBSmNxqdkwn1O6u5/4cAXlYgcnngE/pQNvih8S211obHRyYbWInfJG/Ex9MD2+tBmNzcTXTtJcSSSSHH5jngDAH0oEdxbg5A9wKAzPwO+fegSLfLJoFoR5fUfegXOcHGAT8qAM+XaBzQCCwGDuyPlQWJpV37Q5TIweM7u/f9qA9vNYpFML2KaR8YiaJgAh55PvQRvnYoqA+MThcDnPai4PKWQlH3K6tggjnPaiEmz4ZznBPfFAVWG0AZDH1z2HzoE7lhv8AJIHI/mGRQI8AEeuOMGgndN6pu7V4RJLKY4WDLhypXj0oNL6d+MMS4ttetDdQgDNwAPEwPRh2NZGkabrvTXVZiexvba5aI+ILWZQG3Y4IDdvtQScvTdjK8chtFjkQ+VlYgqPXGKA17daV07apJrV9CsZbELTgbu3YY78UEHf9evJ4K9P6JqGoiR1XxjCUjAJ5OT3NBM9YdSWPTenwy3t7bWbSuBunUthfUhRyT+1BA2vXnS/jGdeo9LnIHljeLwSCe5zgmgejrOz1S3kGhazoaXYGAJ5Sw3e38uaCsJfX02rPD1XfXtvcCXdBJGjLbOO+EK88Y7nIoLB1H1Bb6WkN1ddSQ29io/5MZEjzt7DGTjj2FXNGUfEH4wRaxCtnp2kwGGM7llvBvIOO4XOAe/fNMwZbqusalfLBHfzSvFH+SIgKo+igYqiwWfWV30rpp03p6exJnUPJexQnxuR+Ulu2PkKCrT6jcSiTxZnbxCWcFidxPJJ96BBDlQ35fbFAbahBHJIGO+KAIwg5YnB455oDkKcbW7UAOowSMjOORQcCVXPp+9AqDkHcDmgMNpHPcUBTuzQWCJXcFvKR2Y0CMiqjnz4UcH/6oG8gKluwxyAfSjQ6ylEJBJfv37/OiYQMjbjkZXOSP/FEELAEkNn1waBCXdjORnPoc80CZeTb5wQe2BQAm4y7jlhjvQcWO3cW4GB7ZpgGC5a3uUeNyGQ5GCR+45pgt+l/EzqLTgxj1O5Zc4CSOXCj70wOE+Jd/Pq0V7qVvb3bISAWUBhnuc+/2pgvkHx0soLaNIdKkEiqR5yDg47cYpgresfELSNc1n8VrFtAw2ZBiiywwcgeb14x2xTBYNA13ozUo/GOqWVizDc1nf6crIh/7wOf1rOURvVupdE6ncpFeakiSWsZdbjSLfw1Zs+VVyMHA75xWsFDHU0idTJdf65rT28YKpPvHjKp9Bk49qYK/rGpXF/qU9zPdyzyyMSJJAAx9ifnVlwNZ7vxYEh8GAEHO8DDH5H5U0IPK8jHxSzFQAMnOKgJkFwPT6UBlAII5z3zQCjnA5OKBXeuAT9KABMA208DtxQHRhzgUC3KjJx9z2oAP6/L3NAHC8Hg/XNAcNtGe4oEy5yeaCdLk7yx2qQCAO1AmXZSSexHbPNAhJuLJkgjvzRonuAJy2cd8UCbyOi453Dj7GiYTZyVPPl74oYLJIyq68EH3Gf3oYTDEjLbiP1FEDHOUOdgOfXIBFAm77j5Mnng/WgLI5UE8Eg9iO9AnuJbuQx5wOBQFRxuIbOc54PrQK28ws76F722EyI4d4HJUOPb35yKBm8oeQsi4BPbPb71RyYIHmPGRg00GRsbsHIPY0Bg52AEEseBUCQJyOPXtQDtcdvvjtQCQ/GBwKAuXU4PrQBvZE5IGeO1AffjBJ57UBvEO045HagFWAAzktQKIzBeMg0C5kz5mOG/WgMrDJJ7jmgEnIyOccYoA3cEMRj05oC7/wDeBQTduzEoNxwcZGaAJOWfPNAlISVOT60aIQfkj+amgJ3bnnigKeFGPQUCf/x0Smw4V8exogX/AOY3+/SgKxKxeU459KAgJOckntQJkkcgkGgAAFFz/XQEmJaY7jnk96BM9yPQelAf/wCX7UBv/jagGP8AKB6ZoDf00HMfO/0oAH5TQA/5moECSMDPFAvGASMjPP8AigVX+b60BW7/AHoHEJJD55oDd4snv70CsSjCcDmgVAAbgYoGYJ3nk9qBUAYHAoP/2Q==</binary></FictionBook>
-
+<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink">
+<description>
+<title-info>
+<book-title>Pandoc Test Suite</book-title>
+<author>
+<first-name>John</first-name>
+<last-name>MacFarlane</last-name>
+</author>
+<author>
+<nickname>Anonymous</nickname>
+</author>
+<date>July 17, 2006</date>
+</title-info>
+<document-info>
+<program-used>pandoc</program-used>
+</document-info>
+</description>
+<body>
+<title>
+<p>Pandoc Test Suite</p>
+</title>
+<annotation>
+<p>John MacFarlane</p>
+<p>Anonymous</p>
+<p>July 17, 2006</p>
+</annotation>
+<section>
+<p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Headers</p>
+</title>
+<section>
+<title>
+<p>Level 2 with an embedded link &lt;/url&gt;</p>
+</title>
+<section>
+<title>
+<p>Level 3 with emphasis</p>
+</title>
+<section>
+<title>
+<p>Level 4</p>
+</title>
+<section>
+<title>
+<p>Level 5</p>
+</title>
+</section>
+</section>
+</section>
+</section>
+</section>
+<section>
+<title>
+<p>Level 1</p>
+</title>
+<section>
+<title>
+<p>Level 2 with emphasis</p>
+</title>
+<section>
+<title>
+<p>Level 3</p>
+</title>
+<p>with no blank line</p>
+</section>
+</section>
+<section>
+<title>
+<p>Level 2</p>
+</title>
+<p>with no blank line</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+</section>
+<section>
+<title>
+<p>Paragraphs</p>
+</title>
+<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<empty-line />here.</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Block Quotes</p>
+</title>
+<p>E-mail style:</p>
+<cite>
+<p>This is a block quote. It is pretty short.</p>
+</cite>
+<cite>
+<p>Code in a block quote:</p>
+<empty-line />
+<p>
+<code>sub status {</code>
+</p>
+<p>
+<code> print &quot;working&quot;;</code>
+</p>
+<p>
+<code>}</code>
+</p>
+<empty-line />
+<p>A list:</p>
+<p> 1. item one</p>
+<p> 2. item two</p>
+<p>Nested block quotes:</p>
+<cite>
+<p>nested</p>
+</cite>
+<cite>
+<p>nested</p>
+</cite>
+</cite>
+<p>This should not be a block quote: 2 &gt; 1.</p>
+<p>And a following paragraph.</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Code Blocks</p>
+</title>
+<p>Code:</p>
+<empty-line />
+<p>
+<code>---- (should be four hyphens)</code>
+</p>
+<p>
+<code>
+</code>
+</p>
+<p>
+<code>sub status {</code>
+</p>
+<p>
+<code> print &quot;working&quot;;</code>
+</p>
+<p>
+<code>}</code>
+</p>
+<p>
+<code>
+</code>
+</p>
+<p>
+<code>this code block is indented by one tab</code>
+</p>
+<empty-line />
+<p>And:</p>
+<empty-line />
+<p>
+<code> this code block is indented by two tabs</code>
+</p>
+<p>
+<code>
+</code>
+</p>
+<p>
+<code>These should not be escaped: \$ \\ \&gt; \[ \{</code>
+</p>
+<empty-line />
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Lists</p>
+</title>
+<section>
+<title>
+<p>Unordered</p>
+</title>
+<p>Asterisks tight:</p>
+<p>• asterisk 1</p>
+<p>• asterisk 2</p>
+<p>• asterisk 3</p>
+<p>Asterisks loose:</p>
+<p>• asterisk 1<empty-line />
+</p>
+<p>• asterisk 2<empty-line />
+</p>
+<p>• asterisk 3<empty-line />
+</p>
+<p>Pluses tight:</p>
+<p>• Plus 1</p>
+<p>• Plus 2</p>
+<p>• Plus 3</p>
+<p>Pluses loose:</p>
+<p>• Plus 1<empty-line />
+</p>
+<p>• Plus 2<empty-line />
+</p>
+<p>• Plus 3<empty-line />
+</p>
+<p>Minuses tight:</p>
+<p>• Minus 1</p>
+<p>• Minus 2</p>
+<p>• Minus 3</p>
+<p>Minuses loose:</p>
+<p>• Minus 1<empty-line />
+</p>
+<p>• Minus 2<empty-line />
+</p>
+<p>• Minus 3<empty-line />
+</p>
+</section>
+<section>
+<title>
+<p>Ordered</p>
+</title>
+<p>Tight:</p>
+<p> 1. First</p>
+<p> 2. Second</p>
+<p> 3. Third</p>
+<p>and:</p>
+<p> 1. One</p>
+<p> 2. Two</p>
+<p> 3. Three</p>
+<p>Loose using tabs:</p>
+<p> 1. First<empty-line />
+</p>
+<p> 2. Second<empty-line />
+</p>
+<p> 3. Third<empty-line />
+</p>
+<p>and using spaces:</p>
+<p> 1. One<empty-line />
+</p>
+<p> 2. Two<empty-line />
+</p>
+<p> 3. Three<empty-line />
+</p>
+<p>Multiple paragraphs:</p>
+<p> 1. Item 1, graf one.<empty-line />Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.<empty-line />
+</p>
+<p> 2. Item 2.<empty-line />
+</p>
+<p> 3. Item 3.<empty-line />
+</p>
+</section>
+<section>
+<title>
+<p>Nested</p>
+</title>
+<p>• Tab<p>◦ Tab<p>* Tab</p>
+</p>
+</p>
+<p>Here’s another:</p>
+<p> 1. First</p>
+<p> 2. Second:<p>   • Fee</p>
+<p>   • Fie</p>
+<p>   • Foe</p>
+</p>
+<p> 3. Third</p>
+<p>Same thing but with paragraphs:</p>
+<p> 1. First<empty-line />
+</p>
+<p> 2. Second:<empty-line />
+<p>   • Fee</p>
+<p>   • Fie</p>
+<p>   • Foe</p>
+</p>
+<p> 3. Third<empty-line />
+</p>
+</section>
+<section>
+<title>
+<p>Tabs and spaces</p>
+</title>
+<p>• this is a list item indented with tabs<empty-line />
+</p>
+<p>• this is a list item indented with spaces<empty-line />
+<p>◦ this is an example list item indented with tabs<empty-line />
+</p>
+<p>◦ this is an example list item indented with spaces<empty-line />
+</p>
+</p>
+</section>
+<section>
+<title>
+<p>Fancy list markers</p>
+</title>
+<p> (2) begins with 2</p>
+<p> (3) and now 3<empty-line />with a continuation<empty-line />
+<p> (3) iv. sublist with roman numerals, starting with 4</p>
+<p> (3) v. more items<p> (3) v. (A) a subsublist</p>
+<p> (3) v. (B) a subsublist</p>
+</p>
+</p>
+<p>Nesting:</p>
+<p> A. Upper Alpha<p> A. I. Upper Roman.<p> A. I. (6) Decimal start with 6<p> A. I. (6) c) Lower alpha with paren</p>
+</p>
+</p>
+</p>
+<p>Autonumbering:</p>
+<p> 1. Autonumber.</p>
+<p> 2. More.<p> 2. 1. Nested.</p>
+</p>
+<p>Should not be a list item:</p>
+<p>M.A. 2007</p>
+<p>B. Williams</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+</section>
+<section>
+<title>
+<p>Definition Lists</p>
+</title>
+<p>Tight using spaces:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />
+</p>
+<p>
+<strong>banana</strong>
+</p>
+<p>    yellow fruit<empty-line />
+</p>
+<p>Tight using tabs:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />
+</p>
+<p>
+<strong>banana</strong>
+</p>
+<p>    yellow fruit<empty-line />
+</p>
+<p>Loose:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />
+</p>
+<p>
+<strong>banana</strong>
+</p>
+<p>    yellow fruit<empty-line />
+</p>
+<p>Multiple blocks with italics:</p>
+<p>
+<strong>
+<emphasis>apple</emphasis>
+</strong>
+</p>
+<p>    red fruit<empty-line />    contains seeds, crisp, pleasant to taste<empty-line />
+</p>
+<p>
+<strong>
+<emphasis>orange</emphasis>
+</strong>
+</p>
+<p>    orange fruit<empty-line />
+<empty-line />
+<p>
+<code>    { orange code block }</code>
+</p>
+<empty-line />
+<cite>
+<p>    orange block quote</p>
+</cite>
+</p>
+<p>Multiple definitions, tight:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />    computer<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />    bank<empty-line />
+</p>
+<p>Multiple definitions, loose:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />    computer<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />    bank<empty-line />
+</p>
+<p>Blank line after term, indented marker, alternate markers:</p>
+<p>
+<strong>apple</strong>
+</p>
+<p>    red fruit<empty-line />    computer<empty-line />
+</p>
+<p>
+<strong>orange</strong>
+</p>
+<p>    orange fruit<empty-line />
+<p> 1. sublist</p>
+<p> 2. sublist</p>
+</p>
+</section>
+<section>
+<title>
+<p>HTML Blocks</p>
+</title>
+<p>Simple block on one line:</p>foo<p>And nested without indentation:</p>
+<p>foo</p>bar<p>Interpreted markdown in a table:</p>This is <emphasis>emphasized</emphasis>And this is <strong>strong</strong>
+<p>Here’s a simple block:</p>
+<p>foo</p>
+<p>This should be a code block, though:</p>
+<empty-line />
+<p>
+<code>&lt;div&gt;</code>
+</p>
+<p>
+<code> foo</code>
+</p>
+<p>
+<code>&lt;/div&gt;</code>
+</p>
+<empty-line />
+<p>As should this:</p>
+<empty-line />
+<p>
+<code>&lt;div&gt;foo&lt;/div&gt;</code>
+</p>
+<empty-line />
+<p>Now, nested:</p>foo<p>This should just be an HTML comment:</p>
+<p>Multiline:</p>
+<p>Code block:</p>
+<empty-line />
+<p>
+<code>&lt;!-- Comment --&gt;</code>
+</p>
+<empty-line />
+<p>Just plain comment, with trailing spaces on the line:</p>
+<p>Code:</p>
+<empty-line />
+<p>
+<code>&lt;hr /&gt;</code>
+</p>
+<empty-line />
+<p>Hr’s:</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Inline Markup</p>
+</title>
+<p>This is <emphasis>emphasized</emphasis>, and so <emphasis>is this</emphasis>.</p>
+<p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p>
+<p>An <emphasis>emphasized link<a l:href="#l1" type="note">
+<sup>[1]</sup>
+</a>
+</emphasis>.</p>
+<p>
+<strong>
+<emphasis>This is strong and em.</emphasis>
+</strong>
+</p>
+<p>So is <strong>
+<emphasis>this</emphasis>
+</strong> word.</p>
+<p>
+<strong>
+<emphasis>This is strong and em.</emphasis>
+</strong>
+</p>
+<p>So is <strong>
+<emphasis>this</emphasis>
+</strong> word.</p>
+<p>This is code: <code>&gt;</code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code>&lt;html&gt;</code>.</p>
+<p>
+<strikethrough>This is <emphasis>strikeout</emphasis>.</strikethrough>
+</p>
+<p>Superscripts: a<sup>bc</sup>d a<sup>
+<emphasis>hello</emphasis>
+</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>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Smart quotes, ellipses, dashes</p>
+</title>
+<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 “quoted link<a l:href="#l2" type="note">
+<sup>[2]</sup>
+</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>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>LaTeX</p>
+</title>
+<p>• </p>
+<p>• <code>2+2=4</code>
+</p>
+<p>• <code>x \in y</code>
+</p>
+<p>• <code>\alpha \wedge \omega</code>
+</p>
+<p>• <code>223</code>
+</p>
+<p>• <code>p</code>-Tree</p>
+<p>• Here’s some display math: <code>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</code>
+</p>
+<p>• Here’s one that has a line break in it: <code>\alpha + \omega \times x^2</code>.</p>
+<p>These shouldn’t be math:</p>
+<p>• To get the famous equation, write <code>$e = mc^2$</code>.</p>
+<p>• $22,000 is a <emphasis>lot</emphasis> of money. So is $34,000. (It worked if “lot” is emphasized.)</p>
+<p>• Shoes ($20) and socks ($5).</p>
+<p>• Escaped <code>$</code>: $73 <emphasis>this should be emphasized</emphasis> 23$.</p>
+<p>Here’s a LaTeX table:</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Special Characters</p>
+</title>
+<p>Here is some unicode:</p>
+<p>• I hat: Î</p>
+<p>• o umlaut: ö</p>
+<p>• section: §</p>
+<p>• set membership: ∈</p>
+<p>• copyright: ©</p>
+<p>AT&amp;T has an ampersand in their name.</p>
+<p>AT&amp;T is another way to write it.</p>
+<p>This &amp; that.</p>
+<p>4 &lt; 5.</p>
+<p>6 &gt; 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: &gt;</p>
+<p>Hash: #</p>
+<p>Period: .</p>
+<p>Bang: !</p>
+<p>Plus: +</p>
+<p>Minus: -</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Links</p>
+</title>
+<section>
+<title>
+<p>Explicit</p>
+</title>
+<p>Just a URL<a l:href="#l3" type="note">
+<sup>[3]</sup>
+</a>.</p>
+<p>URL and title<a l:href="#l4" type="note">
+<sup>[4]</sup>
+</a>.</p>
+<p>URL and title<a l:href="#l5" type="note">
+<sup>[5]</sup>
+</a>.</p>
+<p>URL and title<a l:href="#l6" type="note">
+<sup>[6]</sup>
+</a>.</p>
+<p>URL and title<a l:href="#l7" type="note">
+<sup>[7]</sup>
+</a>
+</p>
+<p>URL and title<a l:href="#l8" type="note">
+<sup>[8]</sup>
+</a>
+</p>
+<p>with_underscore<a l:href="#l9" type="note">
+<sup>[9]</sup>
+</a>
+</p>
+<p>Email link<a l:href="#l10" type="note">
+<sup>[10]</sup>
+</a>
+</p>
+<p>Empty<a l:href="#l11" type="note">
+<sup>[11]</sup>
+</a>.</p>
+</section>
+<section>
+<title>
+<p>Reference</p>
+</title>
+<p>Foo bar<a l:href="#l12" type="note">
+<sup>[12]</sup>
+</a>.</p>
+<p>With embedded [brackets]<a l:href="#l13" type="note">
+<sup>[13]</sup>
+</a>.</p>
+<p>b<a l:href="#l14" type="note">
+<sup>[14]</sup>
+</a> by itself should be a link.</p>
+<p>Indented once<a l:href="#l15" type="note">
+<sup>[15]</sup>
+</a>.</p>
+<p>Indented twice<a l:href="#l16" type="note">
+<sup>[16]</sup>
+</a>.</p>
+<p>Indented thrice<a l:href="#l17" type="note">
+<sup>[17]</sup>
+</a>.</p>
+<p>This should [not][] be a link.</p>
+<empty-line />
+<p>
+<code>[not]: /url</code>
+</p>
+<empty-line />
+<p>Foo bar<a l:href="#l18" type="note">
+<sup>[18]</sup>
+</a>.</p>
+<p>Foo biz<a l:href="#l19" type="note">
+<sup>[19]</sup>
+</a>.</p>
+</section>
+<section>
+<title>
+<p>With ampersands</p>
+</title>
+<p>Here’s a link with an ampersand in the URL<a l:href="#l20" type="note">
+<sup>[20]</sup>
+</a>.</p>
+<p>Here’s a link with an amersand in the link text: AT&amp;T<a l:href="#l21" type="note">
+<sup>[21]</sup>
+</a>.</p>
+<p>Here’s an inline link<a l:href="#l22" type="note">
+<sup>[22]</sup>
+</a>.</p>
+<p>Here’s an inline link in pointy braces<a l:href="#l23" type="note">
+<sup>[23]</sup>
+</a>.</p>
+</section>
+<section>
+<title>
+<p>Autolinks</p>
+</title>
+<p>With an ampersand: http://example.com/?foo=1&amp;bar=2<a l:href="#l24" type="note">
+<sup>[24]</sup>
+</a>
+</p>
+<p>• In a list?</p>
+<p>• http://example.com/<a l:href="#l25" type="note">
+<sup>[25]</sup>
+</a>
+</p>
+<p>• It should.</p>
+<p>An e-mail address: nobody@nowhere.net<a l:href="#l26" type="note">
+<sup>[26]</sup>
+</a>
+</p>
+<cite>
+<p>Blockquoted: http://example.com/<a l:href="#l27" type="note">
+<sup>[27]</sup>
+</a>
+</p>
+</cite>
+<p>Auto-links should not occur here: <code>&lt;http://example.com/&gt;</code>
+</p>
+<empty-line />
+<p>
+<code>or here: &lt;http://example.com/&gt;</code>
+</p>
+<empty-line />
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+</section>
+<section>
+<title>
+<p>Images</p>
+</title>
+<p>From “Voyage dans la Lune” by Georges Melies (1902):</p>
+<image l:href="#image1" l:type="imageType" alt="lalune" title="Voyage dans la Lune" />
+<p>Here is a movie <image l:href="#image2" l:type="inlineImageType" alt="movie" /> icon.</p>
+<empty-line />
+<p>——————————</p>
+<empty-line />
+</section>
+<section>
+<title>
+<p>Footnotes</p>
+</title>
+<p>Here is a footnote reference,<a l:href="#n28" type="note">
+<sup>[28]</sup>
+</a> and another.<a l:href="#n29" type="note">
+<sup>[29]</sup>
+</a> This should <emphasis>not</emphasis> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a l:href="#n30" type="note">
+<sup>[30]</sup>
+</a>
+</p>
+<cite>
+<p>Notes can go in quotes.<a l:href="#n31" type="note">
+<sup>[31]</sup>
+</a>
+</p>
+</cite>
+<p> 1. And in list items.<a l:href="#n32" type="note">
+<sup>[32]</sup>
+</a>
+</p>
+<p>This paragraph should not be part of the note, as it is not indented.</p>
+</section>
+</body>
+<body name="notes">
+<section id="l1">
+<title>
+<p>1</p>
+</title>
+<p>
+<code>/url</code>
+</p>
+</section>
+<section id="l2">
+<title>
+<p>2</p>
+</title>
+<p>
+<code>http://example.com/?foo=1&amp;bar=2</code>
+</p>
+</section>
+<section id="l3">
+<title>
+<p>3</p>
+</title>
+<p>
+<code>/url/</code>
+</p>
+</section>
+<section id="l4">
+<title>
+<p>4</p>
+</title>
+<p>title: <code>/url/</code>
+</p>
+</section>
+<section id="l5">
+<title>
+<p>5</p>
+</title>
+<p>title preceded by two spaces: <code>/url/</code>
+</p>
+</section>
+<section id="l6">
+<title>
+<p>6</p>
+</title>
+<p>title preceded by a tab: <code>/url/</code>
+</p>
+</section>
+<section id="l7">
+<title>
+<p>7</p>
+</title>
+<p>title with &quot;quotes&quot; in it: <code>/url/</code>
+</p>
+</section>
+<section id="l8">
+<title>
+<p>8</p>
+</title>
+<p>title with single quotes: <code>/url/</code>
+</p>
+</section>
+<section id="l9">
+<title>
+<p>9</p>
+</title>
+<p>
+<code>/url/with_underscore</code>
+</p>
+</section>
+<section id="l10">
+<title>
+<p>10</p>
+</title>
+<p>
+<code>mailto:nobody@nowhere.net</code>
+</p>
+</section>
+<section id="l11">
+<title>
+<p>11</p>
+</title>
+<p>
+<code>
+</code>
+</p>
+</section>
+<section id="l12">
+<title>
+<p>12</p>
+</title>
+<p>
+<code>/url/</code>
+</p>
+</section>
+<section id="l13">
+<title>
+<p>13</p>
+</title>
+<p>
+<code>/url/</code>
+</p>
+</section>
+<section id="l14">
+<title>
+<p>14</p>
+</title>
+<p>
+<code>/url/</code>
+</p>
+</section>
+<section id="l15">
+<title>
+<p>15</p>
+</title>
+<p>
+<code>/url</code>
+</p>
+</section>
+<section id="l16">
+<title>
+<p>16</p>
+</title>
+<p>
+<code>/url</code>
+</p>
+</section>
+<section id="l17">
+<title>
+<p>17</p>
+</title>
+<p>
+<code>/url</code>
+</p>
+</section>
+<section id="l18">
+<title>
+<p>18</p>
+</title>
+<p>Title with &quot;quotes&quot; inside: <code>/url/</code>
+</p>
+</section>
+<section id="l19">
+<title>
+<p>19</p>
+</title>
+<p>Title with &quot;quote&quot; inside: <code>/url/</code>
+</p>
+</section>
+<section id="l20">
+<title>
+<p>20</p>
+</title>
+<p>
+<code>http://example.com/?foo=1&amp;bar=2</code>
+</p>
+</section>
+<section id="l21">
+<title>
+<p>21</p>
+</title>
+<p>AT&amp;T: <code>http://att.com/</code>
+</p>
+</section>
+<section id="l22">
+<title>
+<p>22</p>
+</title>
+<p>
+<code>/script?foo=1&amp;bar=2</code>
+</p>
+</section>
+<section id="l23">
+<title>
+<p>23</p>
+</title>
+<p>
+<code>/script?foo=1&amp;bar=2</code>
+</p>
+</section>
+<section id="l24">
+<title>
+<p>24</p>
+</title>
+<p>
+<code>http://example.com/?foo=1&amp;bar=2</code>
+</p>
+</section>
+<section id="l25">
+<title>
+<p>25</p>
+</title>
+<p>
+<code>http://example.com/</code>
+</p>
+</section>
+<section id="l26">
+<title>
+<p>26</p>
+</title>
+<p>
+<code>mailto:nobody@nowhere.net</code>
+</p>
+</section>
+<section id="l27">
+<title>
+<p>27</p>
+</title>
+<p>
+<code>http://example.com/</code>
+</p>
+</section>
+<section id="n28">
+<title>
+<p>28</p>
+</title>
+<p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</p>
+</section>
+<section id="n29">
+<title>
+<p>29</p>
+</title>
+<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>
+<empty-line />
+<p>
+<code> { &lt;code&gt; }</code>
+</p>
+<empty-line />
+<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p>
+</section>
+<section id="n30">
+<title>
+<p>30</p>
+</title>
+<p>This is <emphasis>easier</emphasis> to type. Inline notes may contain links<a l:href="#l30" type="note">
+<sup>[30]</sup>
+</a> and <code>]</code> verbatim characters, as well as [bracketed text].</p>
+</section>
+<section id="n31">
+<title>
+<p>31</p>
+</title>
+<p>In quote.</p>
+</section>
+<section id="n32">
+<title>
+<p>32</p>
+</title>
+<p>In list.</p>
+</section>
+</body>
+</FictionBook>
diff --git a/test/writer.haddock b/test/writer.haddock
index 0772331e3..7f783abd1 100644
--- a/test/writer.haddock
+++ b/test/writer.haddock
@@ -560,10 +560,6 @@ Just a </url/ URL>.
Foo </url/ bar>.
-Foo </url/ bar>.
-
-Foo </url/ bar>.
-
With </url/ embedded [brackets]>.
</url/ b> by itself should be a link.
diff --git a/test/writer.html4 b/test/writer.html4
index bac16b14c..89cf07685 100644
--- a/test/writer.html4
+++ b/test/writer.html4
@@ -486,8 +486,6 @@ Blah
<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>
diff --git a/test/writer.html5 b/test/writer.html5
index ee921766c..6762f8198 100644
--- a/test/writer.html5
+++ b/test/writer.html5
@@ -489,8 +489,6 @@ Blah
<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>
diff --git a/test/writer.icml b/test/writer.icml
index b498f568b..6e070e264 100644
--- a/test/writer.icml
+++ b/test/writer.icml
@@ -2566,37 +2566,9 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>Foo </Content>
- </CharacterStyleRange>
- <HyperlinkTextSource Self="htss-14" Name="" Hidden="false">
- <CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
- <Content>bar</Content>
- </CharacterStyleRange>
- </HyperlinkTextSource>
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>.</Content>
- </CharacterStyleRange>
-</ParagraphStyleRange>
-<Br />
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>Foo </Content>
- </CharacterStyleRange>
- <HyperlinkTextSource Self="htss-15" Name="" Hidden="false">
- <CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
- <Content>bar</Content>
- </CharacterStyleRange>
- </HyperlinkTextSource>
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Content>.</Content>
- </CharacterStyleRange>
-</ParagraphStyleRange>
-<Br />
-<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
- <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>With </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-16" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-14" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>embedded [brackets]</Content>
</CharacterStyleRange>
@@ -2607,7 +2579,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
- <HyperlinkTextSource Self="htss-17" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-15" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>b</Content>
</CharacterStyleRange>
@@ -2621,7 +2593,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Indented </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-18" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-16" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>once</Content>
</CharacterStyleRange>
@@ -2635,7 +2607,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Indented </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-19" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-17" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>twice</Content>
</CharacterStyleRange>
@@ -2649,7 +2621,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Indented </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-20" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-18" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>thrice</Content>
</CharacterStyleRange>
@@ -2675,7 +2647,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Foo </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-21" Name="Title with &quot;quotes&quot; inside" Hidden="false">
+ <HyperlinkTextSource Self="htss-19" Name="Title with &quot;quotes&quot; inside" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>bar</Content>
</CharacterStyleRange>
@@ -2689,7 +2661,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Foo </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-22" Name="Title with &quot;quote&quot; inside" Hidden="false">
+ <HyperlinkTextSource Self="htss-20" Name="Title with &quot;quote&quot; inside" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>biz</Content>
</CharacterStyleRange>
@@ -2709,7 +2681,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Here’s a </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-23" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-21" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>link with an ampersand in the URL</Content>
</CharacterStyleRange>
@@ -2723,7 +2695,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Here’s a link with an amersand in the link text: </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-24" Name="AT&amp;T" Hidden="false">
+ <HyperlinkTextSource Self="htss-22" Name="AT&amp;T" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>AT&amp;T</Content>
</CharacterStyleRange>
@@ -2737,7 +2709,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Here’s an </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-25" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-23" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>inline link</Content>
</CharacterStyleRange>
@@ -2751,7 +2723,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Here’s an </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-26" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-24" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>inline link in pointy braces</Content>
</CharacterStyleRange>
@@ -2771,7 +2743,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>With an ampersand: </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-27" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-25" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>http://example.com/?foo=1&amp;bar=2</Content>
</CharacterStyleRange>
@@ -2785,7 +2757,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
</ParagraphStyleRange>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/BulList">
- <HyperlinkTextSource Self="htss-28" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-26" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>http://example.com/</Content>
</CharacterStyleRange>
@@ -2802,7 +2774,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>An e-mail address: </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-29" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-27" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>nobody@nowhere.net</Content>
</CharacterStyleRange>
@@ -2813,7 +2785,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content>Blockquoted: </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-30" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-28" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>http://example.com/</Content>
</CharacterStyleRange>
@@ -2861,20 +2833,20 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Br />
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Figure">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1.00000 0 0 1.00000 75.00000 -75.00000">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 75 -75">
<Properties>
<PathGeometry>
<GeometryPathType PathOpen="false">
<PathPointArray>
- <PathPointType Anchor="-75.00000 -75.00000" LeftDirection="-75.00000 -75.00000" RightDirection="-75.00000 -75.00000" />
- <PathPointType Anchor="-75.00000 75.00000" LeftDirection="-75.00000 75.00000" RightDirection="-75.00000 75.00000" />
- <PathPointType Anchor="75.00000 75.00000" LeftDirection="75.00000 75.00000" RightDirection="75.00000 75.00000" />
- <PathPointType Anchor="75.00000 -75.00000" LeftDirection="75.00000 -75.00000" RightDirection="75.00000 -75.00000" />
+ <PathPointType Anchor="-75 -75" LeftDirection="-75 -75" RightDirection="-75 -75" />
+ <PathPointType Anchor="-75 75" LeftDirection="-75 75" RightDirection="-75 75" />
+ <PathPointType Anchor="75 75" LeftDirection="75 75" RightDirection="75 75" />
+ <PathPointType Anchor="75 -75" LeftDirection="75 -75" RightDirection="75 -75" />
</PathPointArray>
</GeometryPathType>
</PathGeometry>
</Properties>
- <Image Self="ue6" ItemTransform="1.00000 0 0 1.00000 -75.00000 -75.00000">
+ <Image Self="ue6" ItemTransform="1 0 0 1 -75 -75">
<Properties>
<Profile type="string">
$ID/Embedded
@@ -2897,20 +2869,20 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>Here is a movie </Content>
</CharacterStyleRange>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
- <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1.00000 0 0 1.00000 10.00000 -11.00000">
+ <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 10 -11">
<Properties>
<PathGeometry>
<GeometryPathType PathOpen="false">
<PathPointArray>
- <PathPointType Anchor="-10.00000 -11.00000" LeftDirection="-10.00000 -11.00000" RightDirection="-10.00000 -11.00000" />
- <PathPointType Anchor="-10.00000 11.00000" LeftDirection="-10.00000 11.00000" RightDirection="-10.00000 11.00000" />
- <PathPointType Anchor="10.00000 11.00000" LeftDirection="10.00000 11.00000" RightDirection="10.00000 11.00000" />
- <PathPointType Anchor="10.00000 -11.00000" LeftDirection="10.00000 -11.00000" RightDirection="10.00000 -11.00000" />
+ <PathPointType Anchor="-10 -11" LeftDirection="-10 -11" RightDirection="-10 -11" />
+ <PathPointType Anchor="-10 11" LeftDirection="-10 11" RightDirection="-10 11" />
+ <PathPointType Anchor="10 11" LeftDirection="10 11" RightDirection="10 11" />
+ <PathPointType Anchor="10 -11" LeftDirection="10 -11" RightDirection="10 -11" />
</PathPointArray>
</GeometryPathType>
</PathGeometry>
</Properties>
- <Image Self="ue6" ItemTransform="1.00000 0 0 1.00000 -10.00000 -11.00000">
+ <Image Self="ue6" ItemTransform="1 0 0 1 -10 -11">
<Properties>
<Profile type="string">
$ID/Embedded
@@ -3025,7 +2997,7 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Content> to type. Inline notes may contain </Content>
</CharacterStyleRange>
- <HyperlinkTextSource Self="htss-31" Name="" Hidden="false">
+ <HyperlinkTextSource Self="htss-29" Name="" Hidden="false">
<CharacterStyleRange AppliedCharacterStyle="CharacterStyle/Link">
<Content>links</Content>
</CharacterStyleRange>
@@ -3098,118 +3070,104 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
</Story>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//google.com" Name="link" DestinationURL="http://google.com" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-31" Name="http://google.com" Source="htss-31" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-29" Name="http://google.com" Source="htss-29" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//google.com</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//example.com/" Name="link" DestinationURL="http://example.com/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-30" Name="http://example.com/" Source="htss-30" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-28" Name="http://example.com/" Source="htss-28" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//example.com/</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/mailto%3anobody@nowhere.net" Name="link" DestinationURL="mailto:nobody@nowhere.net" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-29" Name="mailto:nobody@nowhere.net" Source="htss-29" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-27" Name="mailto:nobody@nowhere.net" Source="htss-27" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/mailto%3anobody@nowhere.net</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//example.com/" Name="link" DestinationURL="http://example.com/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-28" Name="http://example.com/" Source="htss-28" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-26" Name="http://example.com/" Source="htss-26" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//example.com/</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//example.com/?foo=1&amp;bar=2" Name="link" DestinationURL="http://example.com/?foo=1&amp;bar=2" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-27" Name="http://example.com/?foo=1&amp;bar=2" Source="htss-27" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-25" Name="http://example.com/?foo=1&amp;bar=2" Source="htss-25" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//example.com/?foo=1&amp;bar=2</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//script?foo=1&amp;bar=2" Name="link" DestinationURL="/script?foo=1&amp;bar=2" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-26" Name="/script?foo=1&amp;bar=2" Source="htss-26" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-24" Name="/script?foo=1&amp;bar=2" Source="htss-24" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//script?foo=1&amp;bar=2</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//script?foo=1&amp;bar=2" Name="link" DestinationURL="/script?foo=1&amp;bar=2" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-25" Name="/script?foo=1&amp;bar=2" Source="htss-25" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-23" Name="/script?foo=1&amp;bar=2" Source="htss-23" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//script?foo=1&amp;bar=2</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//att.com/" Name="link" DestinationURL="http://att.com/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-24" Name="http://att.com/" Source="htss-24" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-22" Name="http://att.com/" Source="htss-22" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//att.com/</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination/http%3a//example.com/?foo=1&amp;bar=2" Name="link" DestinationURL="http://example.com/?foo=1&amp;bar=2" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-23" Name="http://example.com/?foo=1&amp;bar=2" Source="htss-23" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-21" Name="http://example.com/?foo=1&amp;bar=2" Source="htss-21" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination/http%3a//example.com/?foo=1&amp;bar=2</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url/" Name="link" DestinationURL="/url/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-22" Name="/url/" Source="htss-22" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-20" Name="/url/" Source="htss-20" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//url/</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url/" Name="link" DestinationURL="/url/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-21" Name="/url/" Source="htss-21" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-19" Name="/url/" Source="htss-19" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//url/</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url" Name="link" DestinationURL="/url" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-20" Name="/url" Source="htss-20" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-18" Name="/url" Source="htss-18" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//url</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url" Name="link" DestinationURL="/url" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-19" Name="/url" Source="htss-19" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-17" Name="/url" Source="htss-17" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//url</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url" Name="link" DestinationURL="/url" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-18" Name="/url" Source="htss-18" Visible="true" DestinationUniqueKey="1">
+ <Hyperlink Self="uf-16" Name="/url" Source="htss-16" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
<Destination type="object">HyperlinkURLDestination//url</Destination>
</Properties>
</Hyperlink>
<HyperlinkURLDestination Self="HyperlinkURLDestination//url/" Name="link" DestinationURL="/url/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-17" Name="/url/" Source="htss-17" Visible="true" DestinationUniqueKey="1">
- <Properties>
- <BorderColor type="enumeration">Black</BorderColor>
- <Destination type="object">HyperlinkURLDestination//url/</Destination>
- </Properties>
- </Hyperlink>
- <HyperlinkURLDestination Self="HyperlinkURLDestination//url/" Name="link" DestinationURL="/url/" DestinationUniqueKey="1" />
- <Hyperlink Self="uf-16" Name="/url/" Source="htss-16" Visible="true" DestinationUniqueKey="1">
- <Properties>
- <BorderColor type="enumeration">Black</BorderColor>
- <Destination type="object">HyperlinkURLDestination//url/</Destination>
- </Properties>
- </Hyperlink>
- <HyperlinkURLDestination Self="HyperlinkURLDestination//url/" Name="link" DestinationURL="/url/" DestinationUniqueKey="1" />
<Hyperlink Self="uf-15" Name="/url/" Source="htss-15" Visible="true" DestinationUniqueKey="1">
<Properties>
<BorderColor type="enumeration">Black</BorderColor>
diff --git a/test/writer.jats b/test/writer.jats
index 07fe24d73..3cb5050c2 100644
--- a/test/writer.jats
+++ b/test/writer.jats
@@ -1267,12 +1267,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{</preformat>
Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.
</p>
<p>
- Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.
- </p>
- <p>
- Foo <ext-link ext-link-type="uri" xlink:href="/url/">bar</ext-link>.
- </p>
- <p>
With <ext-link ext-link-type="uri" xlink:href="/url/">embedded
[brackets]</ext-link>.
</p>
diff --git a/test/writer.latex b/test/writer.latex
index f88621a28..207e30569 100644
--- a/test/writer.latex
+++ b/test/writer.latex
@@ -17,6 +17,12 @@
\usepackage[]{microtype}
\UseMicrotypeSet[protrusion]{basicmath} % disable protrusion for tt fonts
}{}
+\IfFileExists{parskip.sty}{%
+\usepackage{parskip}
+}{% else
+\setlength{\parindent}{0pt}
+\setlength{\parskip}{6pt plus 2pt minus 1pt}
+}
\PassOptionsToPackage{hyphens}{url} % url is loaded by hyperref
\usepackage{fancyvrb}
\usepackage[unicode=true]{hyperref}
@@ -39,12 +45,6 @@
\usepackage[normalem]{ulem}
% avoid problems with \sout in headers with hyperref:
\pdfstringdefDisableCommands{\renewcommand{\sout}{}}
-\IfFileExists{parskip.sty}{%
-\usepackage{parskip}
-}{% else
-\setlength{\parindent}{0pt}
-\setlength{\parskip}{6pt plus 2pt minus 1pt}
-}
\setlength{\emergencystretch}{3em} % prevent overfull lines
\providecommand{\tightlist}{%
\setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
@@ -877,10 +877,6 @@ Just a \href{/url/}{URL}.
Foo \href{/url/}{bar}.
-Foo \href{/url/}{bar}.
-
-Foo \href{/url/}{bar}.
-
With \href{/url/}{embedded {[}brackets{]}}.
\href{/url/}{b} by itself should be a link.
diff --git a/test/writer.man b/test/writer.man
index 907fb4878..f6d0deb92 100644
--- a/test/writer.man
+++ b/test/writer.man
@@ -677,10 +677,6 @@ Empty ().
.PP
Foo bar (/url/).
.PP
-Foo bar (/url/).
-.PP
-Foo bar (/url/).
-.PP
With embedded [brackets] (/url/).
.PP
b (/url/) by itself should be a link.
diff --git a/test/writer.markdown b/test/writer.markdown
index 3fe0f4b3e..d41030785 100644
--- a/test/writer.markdown
+++ b/test/writer.markdown
@@ -647,10 +647,6 @@ Reference
Foo [bar](/url/).
-Foo [bar](/url/).
-
-Foo [bar](/url/).
-
With [embedded \[brackets\]](/url/).
[b](/url/) by itself should be a link.
diff --git a/test/writer.mediawiki b/test/writer.mediawiki
index a0dc15fae..968eef388 100644
--- a/test/writer.mediawiki
+++ b/test/writer.mediawiki
@@ -571,10 +571,6 @@ Just a [[url/|URL]].
Foo [[url/|bar]].
-Foo [[url/|bar]].
-
-Foo [[url/|bar]].
-
With [[url/|embedded [brackets]]].
[[url/|b]] by itself should be a link.
diff --git a/test/writer.ms b/test/writer.ms
index 617ccc752..7e079c55d 100644
--- a/test/writer.ms
+++ b/test/writer.ms
@@ -835,16 +835,6 @@ Foo \c
-- "bar"
\&.
.PP
-Foo \c
-.pdfhref W -D "/url/" -A "\c" \
- -- "bar"
-\&.
-.PP
-Foo \c
-.pdfhref W -D "/url/" -A "\c" \
- -- "bar"
-\&.
-.PP
With \c
.pdfhref W -D "/url/" -A "\c" \
-- "embedded [brackets]"
diff --git a/test/writer.muse b/test/writer.muse
index c19cb8ab2..41d1c9a5b 100644
--- a/test/writer.muse
+++ b/test/writer.muse
@@ -9,47 +9,30 @@ markdown test suite.
* Headers
-#headers
-
** Level 2 with an [[/url][embedded link]]
-#level-2-with-an-embedded-link
-
*** Level 3 with <em>emphasis</em>
-#level-3-with-emphasis
-
**** Level 4
-#level-4
-
***** Level 5
-#level-5
-
* Level 1
-#level-1
-
** Level 2 with <em>emphasis</em>
-#level-2-with-emphasis
-
*** Level 3
-#level-3
with no blank line
** Level 2
-#level-2
with no blank line
----
* Paragraphs
-#paragraphs
Here’s a regular paragraph.
In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item.
@@ -65,7 +48,6 @@ here.
* Block Quotes
-#block-quotes
E-mail style:
<quote>
@@ -105,7 +87,6 @@ And a following paragraph.
* Code Blocks
-#code-blocks
Code:
<example>
@@ -130,11 +111,8 @@ These should not be escaped: \$ \\ \> \[ \{
* Lists
-#lists
-
** Unordered
-#unordered
Asterisks tight:
- asterisk 1
@@ -173,7 +151,6 @@ Minuses loose:
** Ordered
-#ordered
Tight:
1. First
@@ -208,7 +185,6 @@ Multiple paragraphs:
** Nested
-#nested
- Tab
- Tab
- Tab
@@ -234,7 +210,6 @@ Same thing but with paragraphs:
** Tabs and spaces
-#tabs-and-spaces
- this is a list item indented with tabs
- this is a list item indented with spaces
@@ -243,7 +218,6 @@ Same thing but with paragraphs:
** Fancy list markers
-#fancy-list-markers
2. begins with 2
3. and now 3
@@ -277,7 +251,6 @@ B. Williams
* Definition Lists
-#definition-lists
Tight using spaces:
apple :: red fruit
@@ -339,7 +312,6 @@ Blank line after term, indented marker, alternate markers:
* HTML Blocks
-#html-blocks
Simple block on one line:
fooAnd nested without indentation:
@@ -489,7 +461,6 @@ Hr’s:
* Inline Markup
-#inline-markup
This is <em>emphasized</em>, and so <em>is this</em>.
This is <strong>strong</strong>, and so <strong>is this</strong>.
@@ -521,7 +492,6 @@ spaces: a^b c^d, a~b c~d.
* Smart quotes, ellipses, dashes
-#smart-quotes-ellipses-dashes
"Hello," said the spider. "'Shelob' is my name."
'A', 'B', and 'C' are letters.
@@ -543,7 +513,6 @@ Ellipses…and…and….
* LaTeX
-#latex
- <literal style="tex">\cite[22-23]{smith.1899}</literal>
- 2 + 2 <verbatim>=</verbatim> 4
- <em>x</em> ∈ <em>y</em>
@@ -578,7 +547,6 @@ Cat & 1 \\ \hline
* Special Characters
-#special-characters
Here is some unicode:
- I hat: Î
@@ -633,11 +601,8 @@ Minus: -
* Links
-#links
-
** Explicit
-#explicit
Just a [[/url/][URL]].
[[/url/][URL and title]].
@@ -658,11 +623,6 @@ Just a [[/url/][URL]].
** Reference
-#reference
-Foo [[/url/][bar]].
-
-Foo [[/url/][bar]].
-
Foo [[/url/][bar]].
With [[/url/][embedded <verbatim>[brackets]</verbatim>]].
@@ -687,7 +647,6 @@ Foo [[/url/][biz]].
** With ampersands
-#with-ampersands
Here’s a [[http://example.com/?foo=1&bar=2][link with an ampersand in the
URL]].
@@ -699,7 +658,6 @@ Here’s an [[/script?foo=1&bar=2][inline link in pointy braces]].
** Autolinks
-#autolinks
With an ampersand: [[http://example.com/?foo=1&bar=2]]
- In a list?
@@ -723,7 +681,6 @@ or here: <http://example.com/>
* Images
-#images
From "Voyage dans la Lune" by Georges Melies (1902):
[[lalune.jpg][Voyage dans la Lune]]
@@ -734,7 +691,6 @@ Here is a movie [[movie.jpg][movie]] icon.
* Footnotes
-#footnotes
Here is a footnote reference,[1] and another.[2] This should <em>not</em> be a
footnote reference, because it contains a <verbatim>space.[^my</verbatim>
<verbatim>note]</verbatim> Here is an inline note.[3]
diff --git a/test/writer.native b/test/writer.native
index fa234dfc2..0587bddb8 100644
--- a/test/writer.native
+++ b/test/writer.native
@@ -369,8 +369,6 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
-,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
-,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
diff --git a/test/writer.opendocument b/test/writer.opendocument
index 86d88ee27..77c79d13c 100644
--- a/test/writer.opendocument
+++ b/test/writer.opendocument
@@ -1434,10 +1434,6 @@ link</text:span></text:a></text:p>
<text:h text:style-name="Heading_20_2" text:outline-level="2">Reference</text:h>
<text:p text:style-name="First_20_paragraph">Foo
<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">bar</text:span></text:a>.</text:p>
-<text:p text:style-name="Text_20_body">Foo
-<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">bar</text:span></text:a>.</text:p>
-<text:p text:style-name="Text_20_body">Foo
-<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">bar</text:span></text:a>.</text:p>
<text:p text:style-name="Text_20_body">With
<text:a xlink:type="simple" xlink:href="/url/" office:name=""><text:span text:style-name="Definition">embedded
[brackets]</text:span></text:a>.</text:p>
diff --git a/test/writer.opml b/test/writer.opml
index 51b0cb2d5..4e67652d2 100644
--- a/test/writer.opml
+++ b/test/writer.opml
@@ -57,7 +57,7 @@
<outline text="Links">
<outline text="Explicit" _note="Just a [URL](/url/).&#10;&#10;[URL and title](/url/ &quot;title&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by two spaces&quot;).&#10;&#10;[URL and title](/url/ &quot;title preceded by a tab&quot;).&#10;&#10;[URL and title](/url/ &quot;title with &quot;quotes&quot; in it&quot;)&#10;&#10;[URL and title](/url/ &quot;title with single quotes&quot;)&#10;&#10;[with\_underscore](/url/with_underscore)&#10;&#10;[Email link](mailto:nobody@nowhere.net)&#10;&#10;[Empty]().">
</outline>
- <outline text="Reference" _note="Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;Foo [bar](/url/).&#10;&#10;With [embedded \[brackets\]](/url/).&#10;&#10;[b](/url/) by itself should be a link.&#10;&#10;Indented [once](/url).&#10;&#10;Indented [twice](/url).&#10;&#10;Indented [thrice](/url).&#10;&#10;This should \[not\]\[\] be a link.&#10;&#10; [not]: /url&#10;&#10;Foo [bar](/url/ &quot;Title with &quot;quotes&quot; inside&quot;).&#10;&#10;Foo [biz](/url/ &quot;Title with &quot;quote&quot; inside&quot;).">
+ <outline text="Reference" _note="Foo [bar](/url/).&#10;&#10;With [embedded \[brackets\]](/url/).&#10;&#10;[b](/url/) by itself should be a link.&#10;&#10;Indented [once](/url).&#10;&#10;Indented [twice](/url).&#10;&#10;Indented [thrice](/url).&#10;&#10;This should \[not\]\[\] be a link.&#10;&#10; [not]: /url&#10;&#10;Foo [bar](/url/ &quot;Title with &quot;quotes&quot; inside&quot;).&#10;&#10;Foo [biz](/url/ &quot;Title with &quot;quote&quot; inside&quot;).">
</outline>
<outline text="With ampersands" _note="Here’s a [link with an ampersand in the&#10;URL](http://example.com/?foo=1&amp;bar=2).&#10;&#10;Here’s a link with an amersand in the link text:&#10;[AT&amp;T](http://att.com/ &quot;AT&amp;T&quot;).&#10;&#10;Here’s an [inline link](/script?foo=1&amp;bar=2).&#10;&#10;Here’s an [inline link in pointy braces](/script?foo=1&amp;bar=2).">
</outline>
diff --git a/test/writer.org b/test/writer.org
index 96db87449..1ae0ca8f3 100644
--- a/test/writer.org
+++ b/test/writer.org
@@ -737,10 +737,6 @@ Just a [[/url/][URL]].
Foo [[/url/][bar]].
-Foo [[/url/][bar]].
-
-Foo [[/url/][bar]].
-
With [[/url/][embedded [brackets]]].
[[/url/][b]] by itself should be a link.
diff --git a/test/writer.plain b/test/writer.plain
index 175efb608..031c4a3e6 100644
--- a/test/writer.plain
+++ b/test/writer.plain
@@ -594,10 +594,6 @@ Reference
Foo bar.
-Foo bar.
-
-Foo bar.
-
With embedded [brackets].
b by itself should be a link.
diff --git a/test/writer.rst b/test/writer.rst
index 1aeeacacb..e81e79f3f 100644
--- a/test/writer.rst
+++ b/test/writer.rst
@@ -75,6 +75,8 @@ E-mail style:
This is a block quote. It is pretty short.
+..
+
Code in a block quote:
::
@@ -92,6 +94,8 @@ E-mail style:
nested
+ ..
+
nested
This should not be a block quote: 2 > 1.
@@ -342,6 +346,8 @@ Multiple blocks with italics:
{ orange code block }
+ ..
+
orange block quote
Multiple definitions, tight:
@@ -777,10 +783,6 @@ Reference
Foo `bar </url/>`__.
-Foo `bar </url/>`__.
-
-Foo `bar </url/>`__.
-
With `embedded [brackets] </url/>`__.
`b </url/>`__ by itself should be a link.
diff --git a/test/writer.rtf b/test/writer.rtf
index a79ae6fb5..c67c67a83 100644
--- a/test/writer.rtf
+++ b/test/writer.rtf
@@ -350,14 +350,6 @@ Empty
bar
}}}
.\par}
-{\pard \ql \f0 \sa180 \li0 \fi0 Foo {\field{\*\fldinst{HYPERLINK "/url/"}}{\fldrslt{\ul
-bar
-}}}
-.\par}
-{\pard \ql \f0 \sa180 \li0 \fi0 Foo {\field{\*\fldinst{HYPERLINK "/url/"}}{\fldrslt{\ul
-bar
-}}}
-.\par}
{\pard \ql \f0 \sa180 \li0 \fi0 With {\field{\*\fldinst{HYPERLINK "/url/"}}{\fldrslt{\ul
embedded [brackets]
}}}
diff --git a/test/writer.tei b/test/writer.tei
index 986240c86..ecbe92e33 100644
--- a/test/writer.tei
+++ b/test/writer.tei
@@ -754,8 +754,6 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<div type="level2" id="reference">
<head>Reference</head>
<p>Foo <ref target="/url/">bar</ref>.</p>
- <p>Foo <ref target="/url/">bar</ref>.</p>
- <p>Foo <ref target="/url/">bar</ref>.</p>
<p>With <ref target="/url/">embedded [brackets]</ref>.</p>
<p><ref target="/url/">b</ref> by itself should be a link.</p>
<p>Indented <ref target="/url">once</ref>.</p>
diff --git a/test/writer.texinfo b/test/writer.texinfo
index ca87da1a9..f5727d96d 100644
--- a/test/writer.texinfo
+++ b/test/writer.texinfo
@@ -939,10 +939,6 @@ Just a @uref{/url/,URL}.
@anchor{#reference}
Foo @uref{/url/,bar}.
-Foo @uref{/url/,bar}.
-
-Foo @uref{/url/,bar}.
-
With @uref{/url/,embedded [brackets]}.
@uref{/url/,b} by itself should be a link.
diff --git a/test/writer.textile b/test/writer.textile
index 293418ed5..d19b698f9 100644
--- a/test/writer.textile
+++ b/test/writer.textile
@@ -623,10 +623,6 @@ h2(#reference). Reference
Foo "bar":/url/.
-Foo "bar":/url/.
-
-Foo "bar":/url/.
-
With "embedded [brackets]":/url/.
"b":/url/ by itself should be a link.
diff --git a/test/writer.zimwiki b/test/writer.zimwiki
index 7a15bad9d..91f018b52 100644
--- a/test/writer.zimwiki
+++ b/test/writer.zimwiki
@@ -538,10 +538,6 @@ Just a [[url/|URL]].
Foo [[url/|bar]].
-Foo [[url/|bar]].
-
-Foo [[url/|bar]].
-
With [[url/|embedded [brackets]]].
[[url/|b]] by itself should be a link.
diff --git a/test/writers-lang-and-dir.context b/test/writers-lang-and-dir.context
index 66dab9ead..250ee8c59 100644
--- a/test/writers-lang-and-dir.context
+++ b/test/writers-lang-and-dir.context
@@ -4,19 +4,28 @@
style=,
color=,
contrastcolor=]
+
% make chapter, section bookmarks visible when opening document
\placebookmarks[chapter, section, subsection, subsubsection, subsubsubsection, subsubsubsubsection][chapter, section]
\setupinteractionscreen[option=bookmark]
\setuptagging[state=start]
+
% use microtypography
\definefontfeature[default][default][script=latn, protrusion=quality, expansion=quality, itlc=yes, textitalics=yes, onum=yes, pnum=yes]
\definefontfeature[smallcaps][script=latn, protrusion=quality, expansion=quality, smcp=yes, onum=yes, pnum=yes]
\setupalign[hz,hanging]
\setupitaliccorrection[global, always]
+
\setupbodyfontenvironment[default][em=italic] % use italic as em, not slanted
-\usemodule[simplefonts]
-\setmainfontfallback[DejaVu Serif][range={greekandcoptic, greekextended}, force=yes, rscale=auto]
+
+\definefallbackfamily[mainface][rm][DejaVu Serif][preset=range:greek, force=yes]
+\definefontfamily[mainface][rm][Latin Modern Roman]
+\definefontfamily[mainface][mm][Latin Modern Math]
+\definefontfamily[mainface][ss][Latin Modern Sans]
+\definefontfamily[mainface][tt][Latin Modern Typewriter][features=none]
+\setupbodyfont[mainface]
+
\setupwhitespace[medium]
\setuphead[chapter] [style=\tfd,header=empty]
diff --git a/test/writers-lang-and-dir.latex b/test/writers-lang-and-dir.latex
index cba3dd96b..0a7832a91 100644
--- a/test/writers-lang-and-dir.latex
+++ b/test/writers-lang-and-dir.latex
@@ -17,12 +17,31 @@
\usepackage[]{microtype}
\UseMicrotypeSet[protrusion]{basicmath} % disable protrusion for tt fonts
}{}
+\IfFileExists{parskip.sty}{%
+\usepackage{parskip}
+}{% else
+\setlength{\parindent}{0pt}
+\setlength{\parskip}{6pt plus 2pt minus 1pt}
+}
\PassOptionsToPackage{hyphens}{url} % url is loaded by hyperref
\usepackage[unicode=true]{hyperref}
\hypersetup{
pdfborder={0 0 0},
breaklinks=true}
\urlstyle{same} % don't use monospace font for urls
+\setlength{\emergencystretch}{3em} % prevent overfull lines
+\providecommand{\tightlist}{%
+ \setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
+\setcounter{secnumdepth}{0}
+% Redefines (sub)paragraphs to behave more like sections
+\ifx\paragraph\undefined\else
+\let\oldparagraph\paragraph
+\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}}
+\fi
+\ifx\subparagraph\undefined\else
+\let\oldsubparagraph\subparagraph
+\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}}
+\fi
\ifnum 0\ifxetex 1\fi\ifluatex 1\fi=0 % if pdftex
\usepackage[shorthands=off,ngerman,british,nswissgerman,spanish,french,main=english]{babel}
\newcommand{\textgerman}[2][]{\foreignlanguage{ngerman}{#2}}
@@ -35,6 +54,7 @@
\newcommand{\textfrench}[2][]{\foreignlanguage{french}{#2}}
\newenvironment{french}[2][]{\begin{otherlanguage}{french}}{\end{otherlanguage}}
\else
+ % load polyglossia as late as possible as it *could* call bidi if RTL lang (e.g. Hebrew or Arabic)
\usepackage{polyglossia}
\setmainlanguage[]{english}
\setotherlanguage[]{german}
@@ -43,25 +63,6 @@
\setotherlanguage[]{spanish}
\setotherlanguage[]{french}
\fi
-\IfFileExists{parskip.sty}{%
-\usepackage{parskip}
-}{% else
-\setlength{\parindent}{0pt}
-\setlength{\parskip}{6pt plus 2pt minus 1pt}
-}
-\setlength{\emergencystretch}{3em} % prevent overfull lines
-\providecommand{\tightlist}{%
- \setlength{\itemsep}{0pt}\setlength{\parskip}{0pt}}
-\setcounter{secnumdepth}{0}
-% Redefines (sub)paragraphs to behave more like sections
-\ifx\paragraph\undefined\else
-\let\oldparagraph\paragraph
-\renewcommand{\paragraph}[1]{\oldparagraph{#1}\mbox{}}
-\fi
-\ifx\subparagraph\undefined\else
-\let\oldsubparagraph\subparagraph
-\renewcommand{\subparagraph}[1]{\oldsubparagraph{#1}\mbox{}}
-\fi
\ifxetex
% load bidi as late as possible as it modifies e.g. graphicx
\usepackage{bidi}