diff options
33 files changed, 174 insertions, 171 deletions
diff --git a/MANUAL.txt b/MANUAL.txt index ec3499513..2b55b8239 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -706,12 +706,10 @@ Options affecting specific writers than parsing ligatures for quotation marks and dashes. In writing LaTeX or ConTeXt, print unicode quotation mark and dash characters literally, rather than converting them to - the standard ASCII TeX ligatures. Note: normally the `smart` - extension is selected automatically for LaTeX and ConTeXt output, - but it must be specified explicitly if `--no-tex-ligatures` is - selected. If you use literal curly quotes, dashes, and - ellipses in your source, then you may want to use - `--no-tex-ligatures` without `+smart`. + the standard ASCII TeX ligatures. Note: If you use literal + curly quotes, dashes, and ellipses in your source, then you + may want to use disable the `smart` extension in your + source format. `--listings` @@ -3180,6 +3178,22 @@ they cannot contain multiple paragraphs). The syntax is as follows: Inline and regular footnotes may be mixed freely. +Typography +---------- + +#### Extension: `smart` #### + +Interpret straight quotes as curly quotes, `---` as em-dashes, +`--` as en-dashes, and `...` as ellipses. Nonbreaking spaces are +inserted after certain abbreviations, such as "Mr." + +Note: If you are *writing* Markdown, then the `smart` extension +has the reverse effect: what would have been curly quotes comes +out straight. + +If your LaTeX template or any included header file call +for the [`csquotes`] package, pandoc will detect this +automatically and use `\enquote{...}` for quoted text. Citations --------- @@ -3381,21 +3395,6 @@ in pandoc, but may be enabled by adding `+EXTENSION` to the format name, where `EXTENSION` is the name of the extension. Thus, for example, `markdown+hard_line_breaks` is Markdown with hard line breaks. -#### Extension: `smart` #### - -Interpret straight quotes as curly quotes, `---` as em-dashes, -`--` as en-dashes, and `...` as ellipses. Nonbreaking spaces are -inserted after certain abbreviations, such as "Mr." - -Notes: - - * This extension option is selected automatically when the - output format is `latex` or `context`, unless - `--no-tex-ligatures` is used. It has no effect for `latex` input. - * If your LaTeX template or any included header file call - for the [`csquotes`] package, pandoc will detect this - automatically and use `\enquote{...}` for quoted text. - #### Extension: `old_dashes` #### Selects the pandoc <= 1.8.2.1 behavior for parsing smart dashes: @@ -289,14 +289,6 @@ convertWithOpts opts args = do uriFragment = "" } _ -> Nothing - {- TODO - smart is now an extension, but we should prob make - - texligatures one too... - let smartExt = if laTeXInput - then texLigatures - else smart || (texLigatures && - (laTeXOutput || conTeXtOutput)) - -} - let readerOpts = def{ readerStandalone = standalone' , readerParseRaw = parseRaw , readerColumns = columns diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 7278ece61..14422ce39 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -177,6 +177,7 @@ pandocExtensions = extensionsFromList , Ext_implicit_header_references , Ext_line_blocks , Ext_shortcut_reference_links + , Ext_smart ] plainExtensions :: Extensions diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index f9a8a71d5..21e00b033 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -47,13 +47,13 @@ tests = [ testGroup "markdown" [ testGroup "writer" $ writerTests "markdown" ++ lhsWriterTests "markdown" , testGroup "reader" - [ test "basic" ["-r", "markdown+smart", "-w", "native", "-s"] + [ test "basic" ["-r", "markdown", "-w", "native", "-s"] "testsuite.txt" "testsuite.native" , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] "tables.txt" "tables.native" , test "pipe tables" ["-r", "markdown", "-w", "native", "--columns=80"] "pipe-tables.txt" "pipe-tables.native" - , test "more" ["-r", "markdown+smart", "-w", "native", "-s"] + , test "more" ["-r", "markdown", "-w", "native", "-s"] "markdown-reader-more.txt" "markdown-reader-more.native" , lhsReaderTest "markdown+lhs" ] diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index ef060b8ae..1fdb29f2e 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -1,7 +1,6 @@ module Tests.Readers.Docx (tests) where -import Text.Pandoc.Options -import Text.Pandoc.Readers.Native +import Text.Pandoc import Text.Pandoc.Definition import Tests.Helpers import Test.Framework @@ -26,6 +25,9 @@ data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} noNorm :: Pandoc -> NoNormPandoc noNorm = NoNormPandoc +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "docx" } + instance ToString NoNormPandoc where toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d where s = case d of @@ -57,7 +59,7 @@ testCompareWithOpts opts name docxFile nativeFile = buildTest $ testCompareWithOptsIO opts name docxFile nativeFile testCompare :: String -> FilePath -> FilePath -> Test -testCompare = testCompareWithOpts def +testCompare = testCompareWithOpts defopts testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test testForWarningsWithOptsIO opts name docxFile expected = do @@ -70,7 +72,7 @@ testForWarningsWithOpts opts name docxFile expected = buildTest $ testForWarningsWithOptsIO opts name docxFile expected -- testForWarnings :: String -> FilePath -> [String] -> Test --- testForWarnings = testForWarningsWithOpts def +-- testForWarnings = testForWarningsWithOpts defopts getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString) getMedia archivePath mediaPath = do @@ -95,7 +97,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do compareMediaBagIO :: FilePath -> IO Bool compareMediaBagIO docxFile = do df <- B.readFile docxFile - mb <- runIOorExplode (readDocx def df >> P.getMediaBag) + mb <- runIOorExplode (readDocx defopts df >> P.getMediaBag) bools <- mapM (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) (mediaDirectory mb) diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 45e88d90e..d8572b15b 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -9,7 +9,8 @@ import Text.Pandoc.Builder import Text.Pandoc latex :: String -> Pandoc -latex = purely $ readLaTeX def +latex = purely $ readLaTeX def{ + readerExtensions = getDefaultExtensions "latex" } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index ff68b4d3f..65edf7c38 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -9,18 +9,20 @@ import Text.Pandoc.Builder import Text.Pandoc markdown :: String -> Pandoc -markdown = purely $ readMarkdown def +markdown = purely $ readMarkdown def { readerExtensions = + disableExtension Ext_smart pandocExtensions } markdownSmart :: String -> Pandoc markdownSmart = purely $ readMarkdown def { readerExtensions = - enableExtension Ext_smart $ readerExtensions def } + enableExtension Ext_smart pandocExtensions } markdownCDL :: String -> Pandoc markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension - Ext_compact_definition_lists $ readerExtensions def } + Ext_compact_definition_lists pandocExtensions } markdownGH :: String -> Pandoc -markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions } +markdownGH = purely $ readMarkdown def { + readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c @@ -304,7 +306,7 @@ tests = [ testGroup "inline code" ] , testGroup "lhs" [ test (purely $ readMarkdown def{ readerExtensions = enableExtension - Ext_literate_haskell $ readerExtensions def }) + Ext_literate_haskell pandocExtensions }) "inverse bird tracks and html" $ "> a\n\n< b\n\n<div>\n" =?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a" diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs index b0e916336..63283497b 100644 --- a/tests/Tests/Readers/Odt.hs +++ b/tests/Tests/Readers/Odt.hs @@ -1,18 +1,16 @@ module Tests.Readers.Odt (tests) where import Control.Monad ( liftM ) -import Text.Pandoc.Options -import Text.Pandoc.Readers.Native -import Text.Pandoc.Readers.Markdown -import Text.Pandoc.Definition +import Text.Pandoc import Text.Pandoc.Class (runIO) import Tests.Helpers import Test.Framework import qualified Data.ByteString.Lazy as B -import Text.Pandoc.Readers.Odt import Text.Pandoc.Writers.Native (writeNative) import qualified Data.Map as M -import Text.Pandoc.Error + +defopts :: ReaderOptions +defopts = def{ readerExtensions = getDefaultExtensions "odt" } tests :: [Test] tests = testsComparingToMarkdown ++ testsComparingToNative @@ -71,7 +69,9 @@ compareOdtToMarkdown :: TestCreator compareOdtToMarkdown opts odtPath markdownPath = do markdownFile <- Prelude.readFile markdownPath odtFile <- B.readFile odtPath - markdown <- getNoNormVia id "markdown" <$> runIO (readMarkdown opts markdownFile) + markdown <- getNoNormVia id "markdown" <$> + runIO (readMarkdown def{ readerExtensions = pandocExtensions } + markdownFile) odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile) return (odt,markdown) @@ -81,7 +81,7 @@ createTest :: TestCreator -> FilePath -> FilePath -> Test createTest creator name path1 path2 = - buildTest $ liftM (test id name) (creator def path1 path2) + buildTest $ liftM (test id name) (creator defopts path1 path2) {- -- diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index ed29f1377..ef0530b37 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -9,11 +9,11 @@ import Text.Pandoc import Data.List (intersperse) org :: String -> Pandoc -org = purely $ readOrg def - +org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" } + orgSmart :: String -> Pandoc orgSmart = purely $ readOrg def { readerExtensions = - enableExtension Ext_smart $ readerExtensions def } + enableExtension Ext_smart $ getDefaultExtensions "org" } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index aa8a732f1..abefe27d5 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -8,8 +8,11 @@ import Text.Pandoc import Tests.Helpers import Text.Pandoc.Arbitrary() +defopts :: WriterOptions +defopts = def{ writerExtensions = pandocExtensions } + markdown :: (ToPandoc a) => a -> String -markdown = purely (writeMarkdown def) . toPandoc +markdown = purely (writeMarkdown defopts) . toPandoc markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x @@ -84,7 +87,7 @@ noteTestDoc = noteTests :: Test noteTests = testGroup "note and reference location" - [ test (markdownWithOpts def) + [ test (markdownWithOpts defopts) "footnotes at the end of a document" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -105,7 +108,7 @@ noteTests = testGroup "note and reference location" , "" , "[^2]: The second note." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock}) "footnotes at the end of blocks" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -126,7 +129,7 @@ noteTests = testGroup "note and reference location" , "" , "Some more text." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) "footnotes and reference links at the end of blocks" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -149,7 +152,7 @@ noteTests = testGroup "note and reference location" , "" , "Some more text." ]) - , test (markdownWithOpts def{writerReferenceLocation=EndOfSection}) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection}) "footnotes at the end of section" $ noteTestDoc =?> (unlines $ [ "First Header" @@ -179,7 +182,7 @@ shortcutLinkRefsTests = (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> Test - (=:) = test (purely (writeMarkdown def{writerReferenceLinks = True}) . toPandoc) + (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc) in testGroup "Shortcut reference links" [ "Simple link (shortcutable)" =: (para (link "/url" "title" "foo")) diff --git a/tests/fb2/basic.fb2 b/tests/fb2/basic.fb2 index 14b03fbea..ffb2bfbdf 100644 --- a/tests/fb2/basic.fb2 +++ b/tests/fb2/basic.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Top-level title</p></title><section><title><p>Section</p></title><section><title><p>Subsection</p></title><p>This <emphasis>emphasized</emphasis> <strong>strong</strong> <code>verbatim</code> markdown. See this link<a l:href="#l1" type="note"><sup>[1]</sup></a>.</p><p>Ordered list:</p><p> 1. one</p><p> 2. two</p><p> 3. three</p><cite><p>Blockquote is for citatons.</p></cite><empty-line /><p><code>Code</code></p><p><code>block</code></p><p><code>is</code></p><p><code>for</code></p><p><code>code.</code></p><empty-line /><p><strikethrough>Strikeout</strikethrough> is Pandoc's extension. Superscript and subscripts too: H<sub>2</sub>O is a liquid<a l:href="#n2" type="note"><sup>[2]</sup></a>. 2<sup>10</sup> is 1024.</p><p>Math is another Pandoc extension: <code>E = m c^2</code>.</p></section></section></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>http://example.com/</code></p></section><section id="n2"><title><p>2</p></title><p>Sometimes.</p></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Top-level title</p></title><section><title><p>Section</p></title><section><title><p>Subsection</p></title><p>This <emphasis>emphasized</emphasis> <strong>strong</strong> <code>verbatim</code> markdown. See this link<a l:href="#l1" type="note"><sup>[1]</sup></a>.</p><p>Ordered list:</p><p> 1. one</p><p> 2. two</p><p> 3. three</p><cite><p>Blockquote is for citatons.</p></cite><empty-line /><p><code>Code</code></p><p><code>block</code></p><p><code>is</code></p><p><code>for</code></p><p><code>code.</code></p><empty-line /><p><strikethrough>Strikeout</strikethrough> is Pandoc’s extension. Superscript and subscripts too: H<sub>2</sub>O is a liquid<a l:href="#n2" type="note"><sup>[2]</sup></a>. 2<sup>10</sup> is 1024.</p><p>Math is another Pandoc extension: <code>E = m c^2</code>.</p></section></section></section></body><body name="notes"><section id="l1"><title><p>1</p></title><p><code>http://example.com/</code></p></section><section id="n2"><title><p>2</p></title><p>Sometimes.</p></section></body></FictionBook> + diff --git a/tests/fb2/titles.fb2 b/tests/fb2/titles.fb2 index d8fc1e424..9e8d47e36 100644 --- a/tests/fb2/titles.fb2 +++ b/tests/fb2/titles.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Simple title</p></title><p>This example tests if Pandoc doesn't insert forbidden elements in FictionBook titles.</p></section><section><title><p>Emphasized Strong Title</p></title></section><section><title><p>Title with</p><empty-line /><p>line break</p></title></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><title><p>Simple title</p></title><p>This example tests if Pandoc doesn’t insert forbidden elements in FictionBook titles.</p></section><section><title><p>Emphasized Strong Title</p></title></section><section><title><p>Title with</p><empty-line /><p>line break</p></title></section></body></FictionBook> + diff --git a/tests/markdown-citations.native b/tests/markdown-citations.native index d9738fb4f..c77ccbbfc 100644 --- a/tests/markdown-citations.native +++ b/tests/markdown-citations.native @@ -3,15 +3,15 @@ [[Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@nonexistent]"]]] ,[Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@nonexistent"]]] ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30,",Space,Str "with",Space,Str "suffix]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[-@item2",Space,Str "p.",Space,Str "30;",Space,Str "see",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3]"],Space,Str "says",Space,Str "blah."]] - ,[Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@\1087\1091\1085\1082\1090\&3",Space,Str "[p.",Space,Str "12]"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@\1087\1091\1085\1082\1090\&3]"],Str "."]]]] - ,[Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3",Space,Str "p.",Space,Str "34-35]"],Str "."]] - ,[Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "p.",Space,Str "34-35]"],Str "."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.\160\&30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.\160\&30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "30,",Space,Str "with",Space,Str "suffix]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.\160\&30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[-@item2",Space,Str "p.",Space,Str "30;",Space,Str "see",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3]"],Space,Str "says",Space,Str "blah."]] + ,[Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.\160\&12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@\1087\1091\1085\1082\1090\&3",Space,Str "[p.",Space,Str "12]"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@\1087\1091\1085\1082\1090\&3]"],Str "."]]]] + ,[Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.\160\&34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "@\1087\1091\1085\1082\1090\&3",Space,Str "p.",Space,Str "34-35]"],Str "."]] + ,[Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.\160\&34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "p.",Space,Str "34-35]"],Str "."]] ,[Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[see",Space,Str "@item1",Space,Str "chap.",Space,Str "3;",Space,Str "@\1087\1091\1085\1082\1090\&3;",Space,Str "@item2]"],Str "."]]]] - ,[Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] + ,[Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.\160\&33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] ,[Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1",Space,Str "and",Space,Str "nowhere",Space,Str "else]"],Str "."]] - ,[Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item1]"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item2",Space,Str "p.",Space,Str "44]"],Str "."]]]] + ,[Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item1]"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.\160\&44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "[-@item2",Space,Str "p.",Space,Str "44]"],Str "."]]]] ,[Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[*see*",Space,Str "@item1",Space,Str "p.",Space,Str "**32**]"],Str "."]]] ,Header 1 ("references",[],[]) [Str "References"]] diff --git a/tests/tables-rstsubset.native b/tests/tables-rstsubset.native index c98a95541..ecf6911dc 100644 --- a/tests/tables-rstsubset.native +++ b/tests/tables-rstsubset.native @@ -67,8 +67,8 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] -,Para [Str "Table:",Space,Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] +,Para [Str "Table:",Space,Str "Here\8217s",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.175,0.1625,0.1875,0.3625] [[Plain [Str "Centered",Space,Str "Header"]] @@ -82,7 +82,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignDefault,AlignDefault,AlignDefault,AlignDefault] [0.1,0.1,0.1,0.1] [[] @@ -114,4 +114,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",SoftBreak,Str "rows."]]]]] diff --git a/tests/tables.asciidoc b/tests/tables.asciidoc index 2a24544a3..91490a27a 100644 --- a/tests/tables.asciidoc +++ b/tests/tables.asciidoc @@ -32,12 +32,12 @@ Simple table indented two spaces: Multiline table with caption: -.Here's the caption. It may span multiple lines. +.Here’s the caption. It may span multiple lines. [width="78%",cols="^21%,<17%,>20%,<42%",options="header",] |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= Multiline table without caption: @@ -46,7 +46,7 @@ Multiline table without caption: |======================================================================= |Centered Header |Left Aligned |Right Aligned |Default aligned |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= Table without column headers: @@ -63,5 +63,5 @@ Multiline table without column headers: [width="78%",cols="^21%,<17%,>20%,42%",] |======================================================================= |First |row |12.0 |Example of a row that spans multiple lines. -|Second |row |5.0 |Here's another one. Note the blank line between rows. +|Second |row |5.0 |Here’s another one. Note the blank line between rows. |======================================================================= diff --git a/tests/tables.docbook b/tests/tables.docbook index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook +++ b/tests/tables.docbook @@ -222,7 +222,7 @@ </para> <table> <title> - Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. </title> <tgroup cols="4"> <colspec colwidth="15*" align="center" /> @@ -271,7 +271,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -328,7 +328,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -424,7 +424,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> diff --git a/tests/tables.docbook5 b/tests/tables.docbook5 index 6224cf222..f86b1c390 100644 --- a/tests/tables.docbook5 +++ b/tests/tables.docbook5 @@ -222,7 +222,7 @@ </para> <table> <title> - Here's the caption. It may span multiple lines. + Here’s the caption. It may span multiple lines. </title> <tgroup cols="4"> <colspec colwidth="15*" align="center" /> @@ -271,7 +271,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -328,7 +328,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> @@ -424,7 +424,7 @@ 5.0 </entry> <entry> - Here's another one. Note the blank line between rows. + Here’s another one. Note the blank line between rows. </entry> </row> </tbody> diff --git a/tests/tables.dokuwiki b/tests/tables.dokuwiki index 21e61f656..23c0d22cb 100644 --- a/tests/tables.dokuwiki +++ b/tests/tables.dokuwiki @@ -23,16 +23,16 @@ Demonstration of simple table syntax. Multiline table with caption: -Here's the caption. It may span multiple lines. +Here’s the caption. It may span multiple lines. ^ Centered Header ^Left Aligned ^ Right Aligned^Default aligned ^ | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Multiline table without caption: ^ Centered Header ^Left Aligned ^ Right Aligned^Default aligned ^ | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Table without column headers: @@ -43,5 +43,5 @@ Table without column headers: Multiline table without column headers: | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows.| +| Second |row | 5.0|Here’s another one. Note the blank line between rows.| diff --git a/tests/tables.fb2 b/tests/tables.fb2 index f636e9fd4..df285888e 100644 --- a/tests/tables.fb2 +++ b/tests/tables.fb2 @@ -1,2 +1,3 @@ <?xml version="1.0" encoding="UTF-8"?> -<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><p>Simple table with caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Simple table without caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis /></p><p>Simple table indented two spaces:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Multiline table with caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis>Here's the caption. It may span multiple lines.</emphasis></p><p>Multiline table without caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><th align="right" /><th align="left" /><th align="center" /><th align="right" /></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><th align="center" /><th align="left" /><th align="right" /><th align="left" /></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here's another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p></section></body></FictionBook>
\ No newline at end of file +<FictionBook xmlns="http://www.gribuser.ru/xml/fictionbook/2.0" xmlns:l="http://www.w3.org/1999/xlink"><description><title-info /><document-info><program-used>pandoc</program-used></document-info></description><body><title><p /></title><annotation><p></p></annotation><section><p>Simple table with caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Simple table without caption:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis /></p><p>Simple table indented two spaces:</p><table><tr><th align="right">Right</th><th align="left">Left</th><th align="center">Center</th><th align="left">Default</th></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="left">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="left">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="left">1</td></tr></table><p><emphasis>Demonstration of simple table syntax.</emphasis></p><p>Multiline table with caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis>Here’s the caption. It may span multiple lines.</emphasis></p><p>Multiline table without caption:</p><table><tr><th align="center">Centered Header</th><th align="left">Left Aligned</th><th align="right">Right Aligned</th><th align="left">Default aligned</th></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p><p>Table without column headers:</p><table><tr><th align="right" /><th align="left" /><th align="center" /><th align="right" /></tr><tr><td align="right">12</td><td align="left">12</td><td align="center">12</td><td align="right">12</td></tr><tr><td align="right">123</td><td align="left">123</td><td align="center">123</td><td align="right">123</td></tr><tr><td align="right">1</td><td align="left">1</td><td align="center">1</td><td align="right">1</td></tr></table><p><emphasis /></p><p>Multiline table without column headers:</p><table><tr><th align="center" /><th align="left" /><th align="right" /><th align="left" /></tr><tr><td align="center">First</td><td align="left">row</td><td align="right">12.0</td><td align="left">Example of a row that spans multiple lines.</td></tr><tr><td align="center">Second</td><td align="left">row</td><td align="right">5.0</td><td align="left">Here’s another one. Note the blank line between rows.</td></tr></table><p><emphasis /></p></section></body></FictionBook> + diff --git a/tests/tables.haddock b/tests/tables.haddock index f9efdc0de..84a15cce8 100644 --- a/tests/tables.haddock +++ b/tests/tables.haddock @@ -35,12 +35,12 @@ Multiline table with caption: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > -------------------------------------------------------------- > -> Here\'s the caption. It may span multiple lines. +> Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -51,7 +51,7 @@ Multiline table without caption: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > -------------------------------------------------------------- @@ -70,7 +70,7 @@ Multiline table without column headers: > First row 12.0 Example of a row that > spans multiple lines. > -> Second row 5.0 Here\'s another one. Note +> Second row 5.0 Here’s another one. Note > the blank line between > rows. > ----------- ---------- ------------ -------------------------- diff --git a/tests/tables.html b/tests/tables.html index 0a9ea413c..5bb7a7de2 100644 --- a/tests/tables.html +++ b/tests/tables.html @@ -95,7 +95,7 @@ </table> <p>Multiline table with caption:</p> <table style="width:79%;"> -<caption>Here's the caption. It may span multiple lines.</caption> +<caption>Here’s the caption. It may span multiple lines.</caption> <colgroup> <col width="15%" /> <col width="13%" /> @@ -121,7 +121,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> +<td align="left">Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> @@ -152,7 +152,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td align="left">Here's another one. Note the blank line between rows.</td> +<td align="left">Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> @@ -198,7 +198,7 @@ <td align="center">Second</td> <td align="left">row</td> <td align="right">5.0</td> -<td>Here's another one. Note the blank line between rows.</td> +<td>Here’s another one. Note the blank line between rows.</td> </tr> </tbody> </table> diff --git a/tests/tables.icml b/tests/tables.icml index 678f4b7a9..0280cafed 100644 --- a/tests/tables.icml +++ b/tests/tables.icml @@ -476,14 +476,14 @@ <Cell Name="3:2" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar > LeftAlign"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> </Table> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TableCaption"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's the caption. It may span multiple lines.</Content> + <Content>Here’s the caption. It may span multiple lines.</Content> </CharacterStyleRange> </ParagraphStyleRange> <Br /> @@ -578,7 +578,7 @@ <Cell Name="3:2" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar > LeftAlign"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> @@ -748,7 +748,7 @@ <Cell Name="3:1" AppliedCellStyle="CellStyle/Cell"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/TablePar"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> - <Content>Here's another one. Note the blank line between rows.</Content> + <Content>Here’s another one. Note the blank line between rows.</Content> </CharacterStyleRange> </ParagraphStyleRange> </Cell> diff --git a/tests/tables.man b/tests/tables.man index 788b2199d..dd6a3cce9 100644 --- a/tests/tables.man +++ b/tests/tables.man @@ -135,7 +135,7 @@ T} .PP Multiline table with caption: .PP -Here\[aq]s the caption. It may span multiple lines. +Here's the caption. It may span multiple lines. .TS tab(@); cw(10.5n) lw(9.6n) rw(11.4n) lw(23.6n). @@ -165,7 +165,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE @@ -201,7 +201,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE @@ -261,7 +261,7 @@ row T}@T{ 5.0 T}@T{ -Here\[aq]s another one. +Here's another one. Note the blank line between rows. T} .TE diff --git a/tests/tables.mediawiki b/tests/tables.mediawiki index 614c3eea1..ce7c17887 100644 --- a/tests/tables.mediawiki +++ b/tests/tables.mediawiki @@ -75,7 +75,7 @@ Simple table indented two spaces: Multiline table with caption: {| -|+ Here's the caption. It may span multiple lines. +|+ Here’s the caption. It may span multiple lines. !align="center" width="15%"| Centered Header !width="13%"| Left Aligned !align="right" width="16%"| Right Aligned @@ -89,7 +89,7 @@ Multiline table with caption: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} Multiline table without caption: @@ -108,7 +108,7 @@ Multiline table without caption: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} Table without column headers: @@ -141,6 +141,6 @@ Multiline table without column headers: |align="center"| Second | row |align="right"| 5.0 -| Here's another one. Note the blank line between rows. +| Here’s another one. Note the blank line between rows. |} diff --git a/tests/tables.native b/tests/tables.native index a7f4fdcf1..a60f9b586 100644 --- a/tests/tables.native +++ b/tests/tables.native @@ -53,7 +53,7 @@ ,[Plain [Str "1"]] ,[Plain [Str "1"]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"] -,Table [Str "Here's",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] +,Table [Str "Here\8217s",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] ,[Plain [Str "Left",SoftBreak,Str "Aligned"]] ,[Plain [Str "Right",SoftBreak,Str "Aligned"]] @@ -65,7 +65,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] ,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"] ,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375] [[Plain [Str "Centered",SoftBreak,Str "Header"]] @@ -79,7 +79,7 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]] ,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"] ,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0] [[] @@ -111,4 +111,4 @@ ,[[Plain [Str "Second"]] ,[Plain [Str "row"]] ,[Plain [Str "5.0"]] - ,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] + ,[Plain [Str "Here\8217s",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]] diff --git a/tests/tables.opendocument b/tests/tables.opendocument index 0765bb783..c331ecc43 100644 --- a/tests/tables.opendocument +++ b/tests/tables.opendocument @@ -246,12 +246,12 @@ caption:</text:p> <text:p text:style-name="P16">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table4.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> </table:table> -<text:p text:style-name="Table">Here's the caption. It may span multiple +<text:p text:style-name="Table">Here’s the caption. It may span multiple lines.</text:p> <text:p text:style-name="First_20_paragraph">Multiline table without caption:</text:p> @@ -302,7 +302,7 @@ caption:</text:p> <text:p text:style-name="P20">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table5.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> @@ -390,7 +390,7 @@ headers:</text:p> <text:p text:style-name="P30">5.0</text:p> </table:table-cell> <table:table-cell table:style-name="Table7.A1" office:value-type="string"> - <text:p text:style-name="Table_20_Contents">Here's another one. Note the + <text:p text:style-name="Table_20_Contents">Here’s another one. Note the blank line between rows.</text:p> </table:table-cell> </table:table-row> diff --git a/tests/tables.plain b/tests/tables.plain index 4b5754cf9..4c7ebbf82 100644 --- a/tests/tables.plain +++ b/tests/tables.plain @@ -35,12 +35,12 @@ Multiline table with caption: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. -------------------------------------------------------------- - : Here's the caption. It may span multiple lines. + : Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -51,7 +51,7 @@ Multiline table without caption: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. -------------------------------------------------------------- @@ -70,7 +70,7 @@ Multiline table without column headers: First row 12.0 Example of a row that spans multiple lines. - Second row 5.0 Here's another one. Note + Second row 5.0 Here’s another one. Note the blank line between rows. ----------- ---------- ------------ -------------------------- diff --git a/tests/tables.rst b/tests/tables.rst index 25d5932ea..fc7f0b475 100644 --- a/tests/tables.rst +++ b/tests/tables.rst @@ -47,12 +47,12 @@ Multiline table with caption: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ -Table: Here's the caption. It may span multiple lines. +Table: Here’s the caption. It may span multiple lines. Multiline table without caption: @@ -63,7 +63,7 @@ Multiline table without caption: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ @@ -84,7 +84,7 @@ Multiline table without column headers: | First | row | 12.0 | Example of a row that | | | | | spans multiple lines. | +-------------+------------+--------------+----------------------------+ -| Second | row | 5.0 | Here's another one. Note | +| Second | row | 5.0 | Here’s another one. Note | | | | | the blank line between | | | | | rows. | +-------------+------------+--------------+----------------------------+ diff --git a/tests/tables.rtf b/tests/tables.rtf index 60b088082..57030b114 100644 --- a/tests/tables.rtf +++ b/tests/tables.rtf @@ -226,11 +226,11 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} -{\pard \ql \f0 \sa180 \li0 \fi0 Here's the caption. It may span multiple lines.\par} +{\pard \ql \f0 \sa180 \li0 \fi0 Here\u8217's the caption. It may span multiple lines.\par} {\pard \ql \f0 \sa180 \li0 \fi0 Multiline table without caption:\par} { \trowd \trgaph120 @@ -273,7 +273,7 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} @@ -352,7 +352,7 @@ \cell} {{\pard\intbl \qr \f0 \sa0 \li0 \fi0 5.0\par} \cell} -{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here's another one. Note the blank line between rows.\par} +{{\pard\intbl \ql \f0 \sa0 \li0 \fi0 Here\u8217's another one. Note the blank line between rows.\par} \cell} } \intbl\row} diff --git a/tests/tables.tei b/tests/tables.tei index 45b88b1cb..64438e520 100644 --- a/tests/tables.tei +++ b/tests/tables.tei @@ -97,7 +97,7 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> <p>Multiline table without caption:</p> @@ -118,7 +118,7 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> <p>Table without column headers:</p> @@ -166,6 +166,6 @@ <cell><p>Second</p></cell> <cell><p>row</p></cell> <cell><p>5.0</p></cell> - <cell><p>Here's another one. Note the blank line between rows.</p></cell> + <cell><p>Here’s another one. Note the blank line between rows.</p></cell> </row> </table> diff --git a/tests/tables.zimwiki b/tests/tables.zimwiki index 1f02c9908..6da1f7f2c 100644 --- a/tests/tables.zimwiki +++ b/tests/tables.zimwiki @@ -26,18 +26,18 @@ Demonstration of simple table syntax. Multiline table with caption: -Here's the caption. It may span multiple lines. +Here’s the caption. It may span multiple lines. | Centered Header |Left Aligned | Right Aligned|Default aligned | |:-----------------:|:-------------|--------------:|:------------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Multiline table without caption: | Centered Header |Left Aligned | Right Aligned|Default aligned | |:-----------------:|:-------------|--------------:|:------------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows. | +| Second |row | 5.0|Here’s another one. Note the blank line between rows. | Table without column headers: @@ -52,5 +52,5 @@ Multiline table without column headers: | First |row | 12.0|Example of a row that spans multiple lines. | |:--------:|:----|-----:|-----------------------------------------------------| | First |row | 12.0|Example of a row that spans multiple lines. | -| Second |row | 5.0|Here's another one. Note the blank line between rows.| +| Second |row | 5.0|Here’s another one. Note the blank line between rows.| diff --git a/tests/writer.markdown b/tests/writer.markdown index 4f91a803b..3fe0f4b3e 100644 --- a/tests/writer.markdown +++ b/tests/writer.markdown @@ -6,7 +6,7 @@ date: 'July 17, 2006' title: Pandoc Test Suite --- -This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. ------------------------------------------------------------------------------ @@ -43,13 +43,13 @@ with no blank line Paragraphs ========== -Here’s a regular paragraph. +Here's a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. -Here’s one with a bullet. \* criminey. +Here's one with a bullet. \* criminey. There should be a hard line break\ here. @@ -190,7 +190,7 @@ Multiple paragraphs: 1. Item 1, graf one. - Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + Item 1. graf two. The quick brown fox jumped over the lazy dog's back. 2. Item 2. @@ -203,7 +203,7 @@ Nested - Tab - Tab -Here’s another: +Here's another: 1. First 2. Second: @@ -409,7 +409,7 @@ And this is **strong** </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> -Here’s a simple block: +Here's a simple block: <div> @@ -466,7 +466,7 @@ Code: <hr /> -Hr’s: +Hr's: <hr> <hr /> @@ -513,22 +513,22 @@ spaces: a\^b c\^d, a\~b c\~d. Smart quotes, ellipses, dashes ============================== -“Hello,” said the spider. “‘Shelob’ is my name.” +"Hello," said the spider. "'Shelob' is my name." -‘A’, ‘B’, and ‘C’ are letters. +'A', 'B', and 'C' are letters. -‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ +'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.' -‘He said, “I want to go.”’ Were you alive in the 70’s? +'He said, "I want to go."' Were you alive in the 70's? -Here is some quoted ‘`code`’ and a “[quoted -link](http://example.com/?foo=1&bar=2)”. +Here is some quoted '`code`' and a "[quoted +link](http://example.com/?foo=1&bar=2)". -Some dashes: one—two — three—four — five. +Some dashes: one---two --- three---four --- five. -Dashes between numbers: 5–7, 255–66, 1987–1999. +Dashes between numbers: 5--7, 255--66, 1987--1999. -Ellipses…and…and…. +Ellipses...and...and.... ------------------------------------------------------------------------------ @@ -541,19 +541,19 @@ LaTeX - $\alpha \wedge \omega$ - $223$ - $p$-Tree -- Here’s some display math: +- Here's some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ -- Here’s one that has a line break in it: $\alpha + \omega \times x^2$. +- Here's one that has a line break in it: $\alpha + \omega \times x^2$. -These shouldn’t be math: +These shouldn't be math: - To get the famous equation, write `$e = mc^2$`. -- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is +- \$22,000 is a *lot* of money. So is \$34,000. (It worked if "lot" is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. -Here’s a LaTeX table: +Here's a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline @@ -672,14 +672,14 @@ Foo [biz](/url/ "Title with "quote" inside"). With ampersands --------------- -Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). +Here's a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). -Here’s a link with an amersand in the link text: +Here's a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). -Here’s an [inline link](/script?foo=1&bar=2). +Here's an [inline link](/script?foo=1&bar=2). -Here’s an [inline link in pointy braces](/script?foo=1&bar=2). +Here's an [inline link in pointy braces](/script?foo=1&bar=2). Autolinks --------- @@ -703,7 +703,7 @@ Auto-links should not occur here: `<http://example.com/>` Images ====== -From “Voyage dans la Lune” by Georges Melies (1902): +From "Voyage dans la Lune" by Georges Melies (1902): ![lalune](lalune.jpg "Voyage dans la Lune") @@ -727,7 +727,7 @@ This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. -[^2]: Here’s the long note. This one contains multiple blocks. +[^2]: Here's the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). diff --git a/tests/writer.opml b/tests/writer.opml index c94a88f77..261f83426 100644 --- a/tests/writer.opml +++ b/tests/writer.opml @@ -24,7 +24,7 @@ <outline text="Level 2" _note="with no blank line ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break\ here. ------------------------------------------------------------------------"> +<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break here. ------------------------------------------------------------------------"> </outline> <outline text="Block Quotes" _note="E-mail style: > This is a block quote. It is pretty short. > Code in a block quote: > > sub status { > print "working"; > } > > A list: > > 1. item one > 2. item two > > Nested block quotes: > > > nested > > > nested This should not be a block quote: 2 &gt; 1. And a following paragraph. ------------------------------------------------------------------------"> </outline> @@ -39,18 +39,18 @@ </outline> <outline text="Tabs and spaces" _note="- this is a list item indented with tabs - this is a list item indented with spaces - this is an example list item indented with tabs - this is an example list item indented with spaces "> </outline> - <outline text="Fancy list markers" _note="(2) begins with 2 (3) and now 3 with a continuation iv. sublist with roman numerals, starting with 4 v. more items (A) a subsublist (B) a subsublist Nesting: A. Upper Alpha I. Upper Roman. (6) Decimal start with 6 c) Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams ------------------------------------------------------------------------"> + <outline text="Fancy list markers" _note="1. begins with 2 2. and now 3 with a continuation 1. sublist with roman numerals, starting with 4 2. more items 1. a subsublist 2. a subsublist Nesting: 1. Upper Alpha 1. Upper Roman. 1. Decimal start with 6 1. Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Definition Lists" _note="Tight using spaces: apple : red fruit orange : orange fruit banana : yellow fruit Tight using tabs: apple : red fruit orange : orange fruit banana : yellow fruit Loose: apple : red fruit orange : orange fruit banana : yellow fruit Multiple blocks with italics: *apple* : red fruit contains seeds, crisp, pleasant to taste *orange* : orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple : red fruit : computer orange : orange fruit : bank Multiple definitions, loose: apple : red fruit : computer orange : orange fruit : bank Blank line after term, indented marker, alternate markers: apple : red fruit : computer orange : orange fruit 1. sublist 2. sublist "> +<outline text="Definition Lists" _note="Tight using spaces: apple red fruit orange orange fruit banana yellow fruit Tight using tabs: apple red fruit orange orange fruit banana yellow fruit Loose: apple red fruit orange orange fruit banana yellow fruit Multiple blocks with italics: *apple* red fruit contains seeds, crisp, pleasant to taste *orange* orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple red fruit computer orange orange fruit bank Multiple definitions, loose: apple red fruit computer orange orange fruit bank Blank line after term, indented marker, alternate markers: apple red fruit computer orange orange fruit 1. sublist 2. sublist "> </outline> -<outline text="HTML Blocks" _note="Simple block on one line: <div> foo </div> And nested without indentation: <div> <div> <div> foo </div> </div> <div> bar </div> </div> Interpreted markdown in a table: <table> <tr> <td> This is *emphasized* </td> <td> And this is **strong** </td> </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> Here’s a simple block: <div> foo </div> This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: <div> <div> <div> foo </div> </div> </div> This should just be an HTML comment: <!-- Comment --> Multiline: <!-- Blah Blah --> <!-- This is another comment. --> Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: <!-- foo --> Code: <hr /> Hr’s: <hr> <hr /> <hr /> <hr> <hr /> <hr /> <hr class="foo" id="bar" /> <hr class="foo" id="bar" /> <hr class="foo" id="bar"> ------------------------------------------------------------------------"> +<outline text="HTML Blocks" _note="Simple block on one line: foo And nested without indentation: foo bar Interpreted markdown in a table: This is *emphasized* And this is **strong** Here’s a simple block: foo This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: foo This should just be an HTML comment: Multiline: Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: Code: <hr /> Hr’s: ------------------------------------------------------------------------"> </outline> -<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. ~~This is *strikeout*.~~ Superscripts: a^bc^d a^*hello*^ a^hello there^. Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a\^b c\^d, a\~b c\~d. ------------------------------------------------------------------------"> +<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. This is *strikeout*. Superscripts: abcd a*hello* ahello there. Subscripts: H₂O, H₂₃O, Hmany of themO. These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. ------------------------------------------------------------------------"> </outline> <outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.” ‘A’, ‘B’, and ‘C’ are letters. ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ ‘He said, “I want to go.”’ Were you alive in the 70’s? Here is some quoted ‘`code`’ and a “[quoted link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. ------------------------------------------------------------------------"> </outline> -<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} ------------------------------------------------------------------------"> +<outline text="LaTeX" _note="- - 2 + 2 = 4 - *x* ∈ *y* - *α* ∧ *ω* - 223 - *p*-Tree - Here’s some display math: $$\\frac{d}{dx}f(x)=\\lim\_{h\\to 0}\\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: *α* + *ω* × *x*². These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - $22,000 is a *lot* of money. So is $34,000. (It worked if “lot” is emphasized.) - Shoes ($20) and socks ($5). - Escaped `$`: $73 *this should be emphasized* 23$. Here’s a LaTeX table: ------------------------------------------------------------------------"> </outline> <outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 &lt; 5. 6 &gt; 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: \[ Right bracket: \] Left paren: ( Right paren: ) Greater-than: &gt; Hash: \# Period: . Bang: ! Plus: + Minus: - ------------------------------------------------------------------------"> </outline> @@ -66,7 +66,7 @@ </outline> <outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902): ![lalune](lalune.jpg "Voyage dans la Lune") Here is a movie ![movie](movie.jpg) icon. ------------------------------------------------------------------------"> </outline> -<outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be a footnote reference, because it contains a space.\[\^my note\] Here is an inline note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [^2]: Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as \[bracketed text\]. [^4]: In quote. [^5]: In list."> +<outline text="Footnotes" _note="Here is a footnote reference,[1] and another.[2] This should *not* be a footnote reference, because it contains a space.\[^my note\] Here is an inline note.[3] > Notes can go in quotes.[4] 1. And in list items.[5] This paragraph should not be part of the note, as it is not indented. [1] Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [2] Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [3] This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as \[bracketed text\]. [4] In quote. [5] In list."> </outline> </body> </opml> |