aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-11-03 12:01:29 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-11-03 12:03:05 -0700
commit2f652638516fb82fd809842517c07d620e18c40c (patch)
treed46573fa3d5e0bb751215d98f45c132dba429119 /src/Text
parent9a004b86c92119a499d91ae075b5e68c81136795 (diff)
downloadpandoc-2f652638516fb82fd809842517c07d620e18c40c.tar.gz
AsciiDoc writer: use single-line section headers.
The underline style is now deprecated. Previously `--atx-headers` would enable the single-line style; now the single-line style is always used. Closes #5038.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs38
1 files changed, 9 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index ffe5b7473..e17dad47f 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -40,14 +40,11 @@ AsciiDoc: <http://www.methods.co.nz/asciidoc/>
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
import Prelude
import Control.Monad.State.Strict
-import Data.Aeson (Result (..), Value (String), fromJSON, toJSON)
import Data.Char (isPunctuation, isSpace)
import Data.List (intercalate, intersperse, stripPrefix)
-import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, listToMaybe)
import qualified Data.Set as Set
import Data.Text (Text)
-import qualified Data.Text as T
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
@@ -93,20 +90,13 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
(fmap render' . blockListToAsciiDoc opts)
(fmap render' . inlineListToAsciiDoc opts)
meta
- let addTitleLine (String t) = String $
- t <> "\n" <> T.replicate (T.length t) "="
- addTitleLine x = x
- let metadata' = case fromJSON metadata of
- Success m -> toJSON $ M.adjust addTitleLine
- ("title" :: T.Text) m
- _ -> metadata
body <- blockListToAsciiDoc opts blocks
let main = render colwidth body
let context = defField "body" main
$ defField "toc"
(writerTableOfContents opts &&
isJust (writerTemplate opts))
- $defField "titleblock" titleblock metadata'
+ $defField "titleblock" titleblock metadata
case writerTemplate opts of
Nothing -> return main
Just tpl -> renderTemplate' tpl context
@@ -171,27 +161,17 @@ blockToAsciiDoc _ HorizontalRule =
return $ blankline <> text "'''''" <> blankline
blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
contents <- inlineListToAsciiDoc opts inlines
- let len = offset contents
- -- ident seem to be empty most of the time and asciidoc will generate them automatically
- -- so lets make them not show up when null
ids <- gets autoIds
let autoId = uniqueIdent inlines ids
modify $ \st -> st{ autoIds = Set.insert autoId ids }
- let identifier = if null ident || (isEnabled Ext_auto_identifiers opts && ident == autoId)
- then empty else "[[" <> text ident <> "]]"
- let setext = writerSetextHeaders opts
- return
- (if setext
- then
- identifier $$ contents $$
- (case level of
- 1 -> text $ replicate len '-'
- 2 -> text $ replicate len '~'
- 3 -> text $ replicate len '^'
- 4 -> text $ replicate len '+'
- _ -> empty) <> blankline
- else
- identifier $$ text (replicate level '=') <> space <> contents <> blankline)
+ let identifier = if null ident ||
+ (isEnabled Ext_auto_identifiers opts && ident == autoId)
+ then empty
+ else "[[" <> text ident <> "]]"
+ return $ identifier $$
+ nowrap (text (replicate (level + 1) '=') <> space <> contents) <>
+ blankline
+
blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush (
if null classes
then "...." $$ text str $$ "...."