aboutsummaryrefslogtreecommitdiff
path: root/src/Text
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 /src/Text
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.
Diffstat (limited to 'src/Text')
-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
4 files changed, 45 insertions, 29 deletions
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 "+"