aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2023-07-05 09:10:36 -0700
committerJohn MacFarlane <[email protected]>2023-07-05 09:10:36 -0700
commitadba9d460cdf97acd706218c25d16a9337de1834 (patch)
tree50589e7d13b8c065fb19ac501a39b2fc931a06dd
parent7ba9ecfb5a3ef1fe8193daae240761f5b95a6ff3 (diff)
Make modern AsciiDoc the target for `asciidoc`.
The AsciiDoc community now regards the dialect parsed by `asciidoctor` as the official AsciiDoc syntax, so it should be the target of our `asciidoc` format. Closes #8936. The `asciidoc` output format now behaves like `asciidoctor` used to. `asciidoctor` is a deprecated synonynm. For the old `asciidoc` behavior (targeting the Python script), use `asciidoc_legacy`. The templates have been consolidated. Instead of separate `default.asciidoctor` and `default.asciidoc` templates, there is just `default.asciidoc`. Text.Pandoc.Writers.AsciiDoc API changes: - `writeAsciiDoc` now behaves like `writeAsciiDoctor` used to. - `writeAsciiDoctor` is now a deprecated synonym for `writeAsciiDoc`. - New exported function `writeAsciiDocLegacy` behaves like `writeAsciDoc` used to.
-rw-r--r--MANUAL.txt13
-rw-r--r--data/templates/default.asciidoc3
-rw-r--r--data/templates/default.asciidoctor43
-rw-r--r--pandoc.cabal5
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs3
-rw-r--r--src/Text/Pandoc/Templates.hs2
-rw-r--r--src/Text/Pandoc/Writers.hs4
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs65
-rw-r--r--test/Tests/Old.hs2
-rw-r--r--test/Tests/Writers/AsciiDoc.hs2
-rw-r--r--test/command/8437.md2
-rw-r--r--test/command/8665.md2
-rw-r--r--test/writer.asciidoc41
-rw-r--r--test/writer.asciidoc_legacy (renamed from test/writer.asciidoctor)41
14 files changed, 102 insertions, 126 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index a30b15beb..9f79f4a97 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -284,7 +284,9 @@ header when requesting a document from a URL:
: Specify output format. *FORMAT* can be:
::: {#output-formats}
- - `asciidoc` ([AsciiDoc]) or `asciidoctor` ([AsciiDoctor])
+ - `asciidoc` (modern [AsciiDoc] as interpreted by [AsciiDoctor])
+ - `asciidoc_legacy` ([AsciiDoc] as interpreted by [`asciidoc-py`]).
+ - `asciidoctor` (deprecated synonym for `asciidoc`)
- `beamer` ([LaTeX beamer][`beamer`] slide show)
- `bibtex` ([BibTeX] bibliography)
- `biblatex` ([BibLaTeX] bibliography)
@@ -503,6 +505,7 @@ header when requesting a document from a URL:
[Emacs Org mode]: https://orgmode.org
[AsciiDoc]: https://www.methods.co.nz/asciidoc/
[AsciiDoctor]: https://asciidoctor.org/
+[`asciidoc-py`]: https://github.com/asciidoc-py/asciidoc-py
[DZSlides]: https://paulrouget.com/dzslides/
[Word docx]: https://en.wikipedia.org/wiki/Office_Open_XML
[PDF]: https://www.adobe.com/pdf/
@@ -5017,11 +5020,9 @@ reStructuredText
~ It will be rendered using an [interpreted text role `:math:`].
AsciiDoc
- ~ For AsciiDoc output format (`-t asciidoc`) it will appear verbatim
- surrounded by `latexmath:[$...$]` (for inline math) or
- `[latexmath]++++\[...\]+++` (for display math).
- For AsciiDoctor output format (`-t asciidoctor`) the LaTeX delimiters
- (`$..$` and `\[..\]`) are omitted.
+ ~ For AsciiDoc output math will appear verbatim surrounded by
+ `latexmath:[...]`. For `asciidoc_legacy` the bracketed
+ material will also include inline or display math delimiters.
Texinfo
~ It will be rendered inside a `@math` command.
diff --git a/data/templates/default.asciidoc b/data/templates/default.asciidoc
index ebe70914d..e20384989 100644
--- a/data/templates/default.asciidoc
+++ b/data/templates/default.asciidoc
@@ -17,6 +17,9 @@ $endif$
$if(toc)$
:toc:
$endif$
+$if(math)$
+:stem: latexmath
+$endif$
$endif$
$if(abstract)$
diff --git a/data/templates/default.asciidoctor b/data/templates/default.asciidoctor
deleted file mode 100644
index e20384989..000000000
--- a/data/templates/default.asciidoctor
+++ /dev/null
@@ -1,43 +0,0 @@
-$if(titleblock)$
-= $title$
-$if(author)$
-$for(author)$$author$$sep$; $endfor$
-$if(date)$
-$date$
-$endif$
-$elseif(date)$
-:revdate: $date$
-$endif$
-$if(keywords)$
-:keywords: $for(keywords)$$keywords$$sep$, $endfor$
-$endif$
-$if(lang)$
-:lang: $lang$
-$endif$
-$if(toc)$
-:toc:
-$endif$
-$if(math)$
-:stem: latexmath
-$endif$
-
-$endif$
-$if(abstract)$
-[abstract]
-== Abstract
-$abstract$
-
-$endif$
-$for(header-includes)$
-$header-includes$
-
-$endfor$
-$for(include-before)$
-$include-before$
-
-$endfor$
-$body$
-$for(include-after)$
-
-$include-after$
-$endfor$
diff --git a/pandoc.cabal b/pandoc.cabal
index d6d1dceaa..25ff252cf 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -86,7 +86,6 @@ data-files:
data/templates/default.revealjs
data/templates/default.dzslides
data/templates/default.asciidoc
- data/templates/default.asciidoctor
data/templates/default.haddock
data/templates/default.textile
data/templates/default.org
@@ -313,7 +312,7 @@ extra-source-files:
test/tables.opendocument
test/tables.org
test/tables.asciidoc
- test/tables.asciidoctor
+ test/tables.asciidoc_legacy
test/tables.haddock
test/tables.texinfo
test/tables.typst
@@ -351,7 +350,7 @@ extra-source-files:
test/writer.opendocument
test/writer.org
test/writer.asciidoc
- test/writer.asciidoctor
+ test/writer.asciidoc_legacy
test/writer.haddock
test/writer.rst
test/writer.icml
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 7f5d844e4..d87c36a36 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -93,6 +93,9 @@ optToOutputSettings scriptingEngine opts = do
return (defaultOutputFlavor,Nothing)
Just f -> return (f, Nothing)
+ when (format == "asciidoctor") $ do
+ report $ Deprecated "asciidoctor" "use asciidoc instead"
+
let makeSandboxed pureWriter =
let files = maybe id (:) (optReferenceDoc opts) .
maybe id (:) (optEpubMetadata opts) .
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 433d1f720..bc182be7f 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -106,6 +106,8 @@ getDefaultTemplate format = do
"fb2" -> return ""
"pptx" -> return ""
"ipynb" -> return ""
+ "asciidoctor" -> getDefaultTemplate "asciidoc"
+ "asciidoc_legacy" -> getDefaultTemplate "asciidoc"
"odt" -> getDefaultTemplate "opendocument"
"html" -> getDefaultTemplate "html5"
"docbook" -> getDefaultTemplate "docbook5"
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index c78b00dcf..bc0f9bb2a 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -20,6 +20,7 @@ module Text.Pandoc.Writers
Writer(..)
, writers
, writeAsciiDoc
+ , writeAsciiDocLegacy
, writeAsciiDoctor
, writeBeamer
, writeBibTeX
@@ -183,7 +184,8 @@ writers = [
,("rtf" , TextWriter writeRTF)
,("org" , TextWriter writeOrg)
,("asciidoc" , TextWriter writeAsciiDoc)
- ,("asciidoctor" , TextWriter writeAsciiDoctor)
+ ,("asciidoctor" , TextWriter writeAsciiDoc)
+ ,("asciidoc_legacy" , TextWriter writeAsciiDocLegacy)
,("haddock" , TextWriter writeHaddock)
,("commonmark" , TextWriter writeCommonMark)
,("commonmark_x" , TextWriter writeCommonMark)
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 6d96d38b8..a4f4809e4 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -19,7 +19,11 @@ that it has omitted the construct.
AsciiDoc: <http://www.methods.co.nz/asciidoc/>
-}
-module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc, writeAsciiDoctor) where
+module Text.Pandoc.Writers.AsciiDoc (
+ writeAsciiDoc,
+ writeAsciiDocLegacy,
+ writeAsciiDoctor
+ ) where
import Control.Monad (foldM)
import Control.Monad.State.Strict
( StateT, MonadState(get), gets, modify, evalStateT )
@@ -49,7 +53,7 @@ data WriterState = WriterState { defListMarker :: Text
, bulletListLevel :: Int
, intraword :: Bool
, autoIds :: Set.Set Text
- , asciidoctorVariant :: Bool
+ , legacy :: Bool
, inList :: Bool
, hasMath :: Bool
-- |0 is no table
@@ -64,7 +68,7 @@ defaultWriterState = WriterState { defListMarker = "::"
, bulletListLevel = 0
, intraword = False
, autoIds = Set.empty
- , asciidoctorVariant = False
+ , legacy = False
, inList = False
, hasMath = False
, tableNestingLevel = 0
@@ -75,11 +79,16 @@ writeAsciiDoc :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeAsciiDoc opts document =
evalStateT (pandocToAsciiDoc opts document) defaultWriterState
--- | Convert Pandoc to AsciiDoctor compatible AsciiDoc.
+{-# DEPRECATED writeAsciiDoctor "Use writeAsciiDoc instead" #-}
+-- | Deprecated synonym of 'writeAsciiDoc'.
writeAsciiDoctor :: PandocMonad m => WriterOptions -> Pandoc -> m Text
-writeAsciiDoctor opts document =
+writeAsciiDoctor = writeAsciiDoc
+
+-- | Convert Pandoc to legacy AsciiDoc.
+writeAsciiDocLegacy :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeAsciiDocLegacy opts document =
evalStateT (pandocToAsciiDoc opts document)
- defaultWriterState{ asciidoctorVariant = True }
+ defaultWriterState{ legacy = True }
type ADW = StateT WriterState
@@ -101,7 +110,7 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
$ defField "toc"
(writerTableOfContents opts &&
isJust (writerTemplate opts))
- $ defField "math" (hasMath st)
+ $ defField "math" (hasMath st && not (legacy st))
$ defField "titleblock" titleblock metadata
return $ render colwidth $
case writerTemplate opts of
@@ -364,10 +373,10 @@ bulletListItemToAsciiDoc :: PandocMonad m
bulletListItemToAsciiDoc opts blocks = do
lev <- gets bulletListLevel
modify $ \s -> s{ bulletListLevel = lev + 1 }
- isAsciidoctor <- gets asciidoctorVariant
- let blocksWithTasks = if isAsciidoctor
- then (taskListItemToAsciiDoc blocks)
- else blocks
+ isLegacy <- gets legacy
+ let blocksWithTasks = if isLegacy
+ then blocks
+ else (taskListItemToAsciiDoc blocks)
contents <- foldM (addBlock opts) empty blocksWithTasks
modify $ \s -> s{ bulletListLevel = lev }
let marker = text (replicate (lev + 1) '*')
@@ -526,38 +535,38 @@ inlineToAsciiDoc opts (Subscript lst) = do
return $ "~" <> contents <> "~"
inlineToAsciiDoc opts (SmallCaps lst) = inlineListToAsciiDoc opts lst
inlineToAsciiDoc opts (Quoted qt lst) = do
- isAsciidoctor <- gets asciidoctorVariant
+ isLegacy <- gets legacy
inlineListToAsciiDoc opts $
case qt of
SingleQuote
- | isAsciidoctor -> [Str "'`"] ++ lst ++ [Str "`'"]
- | otherwise -> [Str "`"] ++ lst ++ [Str "'"]
+ | isLegacy -> [Str "`"] ++ lst ++ [Str "'"]
+ | otherwise -> [Str "'`"] ++ lst ++ [Str "`'"]
DoubleQuote
- | isAsciidoctor -> [Str "\"`"] ++ lst ++ [Str "`\""]
- | otherwise -> [Str "``"] ++ lst ++ [Str "''"]
+ | isLegacy -> [Str "``"] ++ lst ++ [Str "''"]
+ | otherwise -> [Str "\"`"] ++ lst ++ [Str "`\""]
inlineToAsciiDoc _ (Code _ str) = do
- isAsciidoctor <- gets asciidoctorVariant
+ isLegacy <- gets legacy
let escChar '`' = "\\'"
escChar c = T.singleton c
let contents = literal (T.concatMap escChar str)
return $
- if isAsciidoctor
- then text "`+" <> contents <> "+`"
- else text "`" <> contents <> "`"
+ if isLegacy
+ then text "`" <> contents <> "`"
+ else text "`+" <> contents <> "+`"
inlineToAsciiDoc _ (Str str) = escapeString str
inlineToAsciiDoc _ (Math InlineMath str) = do
- isAsciidoctor <- gets asciidoctorVariant
+ isLegacy <- gets legacy
modify $ \st -> st{ hasMath = True }
- let content = if isAsciidoctor
- then literal str
- else "$" <> literal str <> "$"
+ let content = if isLegacy
+ then "$" <> literal str <> "$"
+ else literal str
return $ "latexmath:[" <> content <> "]"
inlineToAsciiDoc _ (Math DisplayMath str) = do
- isAsciidoctor <- gets asciidoctorVariant
+ isLegacy <- gets legacy
modify $ \st -> st{ hasMath = True }
- let content = if isAsciidoctor
- then literal str
- else "\\[" <> literal str <> "\\]"
+ let content = if isLegacy
+ then "\\[" <> literal str <> "\\]"
+ else literal str
inlist <- gets inList
let sepline = if inlist
then text "+"
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 81a5adbf2..35ab18686 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -178,7 +178,7 @@ tests pandocPath =
"tikiwiki-reader.tikiwiki" "tikiwiki-reader.native" ]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests' f)
[ "opendocument" , "context" , "texinfo", "icml", "tei"
- , "man" , "plain" , "asciidoc", "asciidoctor"
+ , "man" , "plain" , "asciidoc", "asciidoc_legacy"
, "xwiki", "zimwiki"
]
, testGroup "writers-lang-and-dir"
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index d2b5d5183..642d0ad65 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -12,7 +12,7 @@ asciidoc :: (ToPandoc a) => a -> String
asciidoc = unpack . purely (writeAsciiDoc def) . toPandoc
asciidoctor :: (ToPandoc a) => a -> String
-asciidoctor = unpack . purely (writeAsciiDoctor def) . toPandoc
+asciidoctor = unpack . purely (writeAsciiDoc def) . toPandoc
testAsciidoc :: (ToString a, ToPandoc a)
=> String
diff --git a/test/command/8437.md b/test/command/8437.md
index fcd416239..ab416955d 100644
--- a/test/command/8437.md
+++ b/test/command/8437.md
@@ -1,5 +1,5 @@
```
-% pandoc -f markdown -t asciidoctor
+% pandoc -f markdown -t asciidoc
[![alt](https://img.shields.io/badge/License-Apache%202.0-blue.svg "title")](http://www.apache.org/licenses/LICENSE-2.0)
^D
http://www.apache.org/licenses/LICENSE-2.0[image:https://img.shields.io/badge/License-Apache%202.0-blue.svg[alt,title="title"]]
diff --git a/test/command/8665.md b/test/command/8665.md
index 15d926d26..8f54efedd 100644
--- a/test/command/8665.md
+++ b/test/command/8665.md
@@ -1,5 +1,5 @@
```
-% pandoc -f docbook -t asciidoctor
+% pandoc -f docbook -t asciidoc
<informaltable frame="all" rowsep="1" colsep="1">
<tgroup cols="1">
<thead>
diff --git a/test/writer.asciidoc b/test/writer.asciidoc
index 87a585174..a650cd7e5 100644
--- a/test/writer.asciidoc
+++ b/test/writer.asciidoc
@@ -1,6 +1,7 @@
= Pandoc Test Suite
John MacFarlane; Anonymous
July 17, 2006
+:stem: latexmath
This is a set of tests for pandoc. Most of them are adapted from John Gruber’s
markdown test suite.
@@ -423,7 +424,7 @@ So is *_this_* word.
So is *_this_* word.
-This is code: `>`, `$`, `\`, `\$`, `<html>`.
+This is code: `+>+`, `+$+`, `+\+`, `+\$+`, `+<html>+`.
[line-through]#This is _strikeout_.#
@@ -438,16 +439,16 @@ 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 ``http://example.com/?foo=1&bar=2[quoted
-link]''.
+Here is some quoted '``+code+``' and a "`http://example.com/?foo=1&bar=2[quoted
+link]`".
Some dashes: one—two — three—four — five.
@@ -460,27 +461,27 @@ Ellipses…and…and….
== LaTeX
*
-* latexmath:[$2+2=4$]
-* latexmath:[$x \in y$]
-* latexmath:[$\alpha \wedge \omega$]
-* latexmath:[$223$]
-* latexmath:[$p$]-Tree
+* latexmath:[2+2=4]
+* latexmath:[x \in y]
+* latexmath:[\alpha \wedge \omega]
+* latexmath:[223]
+* latexmath:[p]-Tree
* Here’s some display math:
+
[latexmath]
++++
-\[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\]
+\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:
-latexmath:[$\alpha + \omega \times x^2$].
+latexmath:[\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
+* 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$.
+* Escaped `+$+`: $73 _this should be emphasized_ 23$.
Here’s a LaTeX table:
@@ -610,7 +611,7 @@ ____
Blockquoted: http://example.com/
____
-Auto-links should not occur here: `<http://example.com/>`
+Auto-links should not occur here: `+<http://example.com/>+`
....
or here: <http://example.com/>
@@ -620,7 +621,7 @@ or here: <http://example.com/>
== Images
-From ``Voyage dans la Lune'' by Georges Melies (1902):
+From "`Voyage dans la Lune`" by Georges Melies (1902):
.lalune
image::lalune.jpg[lalune,title="Voyage dans la Lune"]
@@ -636,7 +637,7 @@ after the footnote reference. It need not be placed at the end of the document.]
and another.[multiblock footnote omitted] This should _not_ be a footnote
reference, because it contains a space.[^my note] Here is an inline
note.footnote:[This is _easier_ to type. Inline notes may contain
-http://google.com[links] and `]` verbatim characters, as well as [bracketed
+http://google.com[links] and `+]+` verbatim characters, as well as [bracketed
text].]
____
diff --git a/test/writer.asciidoctor b/test/writer.asciidoc_legacy
index a650cd7e5..87a585174 100644
--- a/test/writer.asciidoctor
+++ b/test/writer.asciidoc_legacy
@@ -1,7 +1,6 @@
= Pandoc Test Suite
John MacFarlane; Anonymous
July 17, 2006
-:stem: latexmath
This is a set of tests for pandoc. Most of them are adapted from John Gruber’s
markdown test suite.
@@ -424,7 +423,7 @@ So is *_this_* word.
So is *_this_* word.
-This is code: `+>+`, `+$+`, `+\+`, `+\$+`, `+<html>+`.
+This is code: `>`, `$`, `\`, `\$`, `<html>`.
[line-through]#This is _strikeout_.#
@@ -439,16 +438,16 @@ 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 "`http://example.com/?foo=1&bar=2[quoted
-link]`".
+Here is some quoted ``code`' and a ``http://example.com/?foo=1&bar=2[quoted
+link]''.
Some dashes: one—two — three—four — five.
@@ -461,27 +460,27 @@ Ellipses…and…and….
== LaTeX
*
-* latexmath:[2+2=4]
-* latexmath:[x \in y]
-* latexmath:[\alpha \wedge \omega]
-* latexmath:[223]
-* latexmath:[p]-Tree
+* latexmath:[$2+2=4$]
+* latexmath:[$x \in y$]
+* latexmath:[$\alpha \wedge \omega$]
+* latexmath:[$223$]
+* latexmath:[$p$]-Tree
* Here’s some display math:
+
[latexmath]
++++
-\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}
+\[\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:
-latexmath:[\alpha + \omega \times x^2].
+latexmath:[$\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
+* 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$.
+* Escaped `$`: $73 _this should be emphasized_ 23$.
Here’s a LaTeX table:
@@ -611,7 +610,7 @@ ____
Blockquoted: http://example.com/
____
-Auto-links should not occur here: `+<http://example.com/>+`
+Auto-links should not occur here: `<http://example.com/>`
....
or here: <http://example.com/>
@@ -621,7 +620,7 @@ or here: <http://example.com/>
== Images
-From "`Voyage dans la Lune`" by Georges Melies (1902):
+From ``Voyage dans la Lune'' by Georges Melies (1902):
.lalune
image::lalune.jpg[lalune,title="Voyage dans la Lune"]
@@ -637,7 +636,7 @@ after the footnote reference. It need not be placed at the end of the document.]
and another.[multiblock footnote omitted] This should _not_ be a footnote
reference, because it contains a space.[^my note] Here is an inline
note.footnote:[This is _easier_ to type. Inline notes may contain
-http://google.com[links] and `+]+` verbatim characters, as well as [bracketed
+http://google.com[links] and `]` verbatim characters, as well as [bracketed
text].]
____