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.
This commit is contained in:
John MacFarlane 2018-11-03 12:01:29 -07:00
parent 9a004b86c9
commit 2f65263851
4 changed files with 43 additions and 94 deletions

View file

@ -882,7 +882,7 @@ Options affecting specific writers {.options}
`--atx-headers` `--atx-headers`
: Use ATX-style headers in Markdown and AsciiDoc output. The default is : Use ATX-style headers in Markdown output. The default is
to use setext-style headers for levels 1-2, and then ATX headers. to use setext-style headers for levels 1-2, and then ATX headers.
(Note: for `gfm` output, ATX headers are always used.) (Note: for `gfm` output, ATX headers are always used.)

View file

@ -1,5 +1,5 @@
$if(titleblock)$ $if(titleblock)$
$title$ = $title$
$if(author)$ $if(author)$
$for(author)$$author$$sep$; $endfor$ $for(author)$$author$$sep$; $endfor$
$endif$ $endif$

View file

@ -40,14 +40,11 @@ AsciiDoc: <http://www.methods.co.nz/asciidoc/>
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
import Prelude import Prelude
import Control.Monad.State.Strict import Control.Monad.State.Strict
import Data.Aeson (Result (..), Value (String), fromJSON, toJSON)
import Data.Char (isPunctuation, isSpace) import Data.Char (isPunctuation, isSpace)
import Data.List (intercalate, intersperse, stripPrefix) import Data.List (intercalate, intersperse, stripPrefix)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, listToMaybe) import Data.Maybe (fromMaybe, isJust, listToMaybe)
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Class (PandocMonad, report) import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.ImageSize import Text.Pandoc.ImageSize
@ -93,20 +90,13 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do
(fmap render' . blockListToAsciiDoc opts) (fmap render' . blockListToAsciiDoc opts)
(fmap render' . inlineListToAsciiDoc opts) (fmap render' . inlineListToAsciiDoc opts)
meta 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 body <- blockListToAsciiDoc opts blocks
let main = render colwidth body let main = render colwidth body
let context = defField "body" main let context = defField "body" main
$ defField "toc" $ defField "toc"
(writerTableOfContents opts && (writerTableOfContents opts &&
isJust (writerTemplate opts)) isJust (writerTemplate opts))
$defField "titleblock" titleblock metadata' $defField "titleblock" titleblock metadata
case writerTemplate opts of case writerTemplate opts of
Nothing -> return main Nothing -> return main
Just tpl -> renderTemplate' tpl context Just tpl -> renderTemplate' tpl context
@ -171,27 +161,17 @@ blockToAsciiDoc _ HorizontalRule =
return $ blankline <> text "'''''" <> blankline return $ blankline <> text "'''''" <> blankline
blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
contents <- inlineListToAsciiDoc opts inlines 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 ids <- gets autoIds
let autoId = uniqueIdent inlines ids let autoId = uniqueIdent inlines ids
modify $ \st -> st{ autoIds = Set.insert autoId ids } modify $ \st -> st{ autoIds = Set.insert autoId ids }
let identifier = if null ident || (isEnabled Ext_auto_identifiers opts && ident == autoId) let identifier = if null ident ||
then empty else "[[" <> text ident <> "]]" (isEnabled Ext_auto_identifiers opts && ident == autoId)
let setext = writerSetextHeaders opts then empty
return else "[[" <> text ident <> "]]"
(if setext return $ identifier $$
then nowrap (text (replicate (level + 1) '=') <> space <> contents) <>
identifier $$ contents $$ blankline
(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)
blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush ( blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush (
if null classes if null classes
then "...." $$ text str $$ "...." then "...." $$ text str $$ "...."

View file

@ -1,5 +1,4 @@
Pandoc Test Suite = Pandoc Test Suite
=================
John MacFarlane; Anonymous John MacFarlane; Anonymous
July 17, 2006 July 17, 2006
@ -8,40 +7,31 @@ markdown test suite.
''''' '''''
Headers == Headers
-------
Level 2 with an link:/url[embedded link] === Level 2 with an link:/url[embedded link]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Level 3 with _emphasis_ ==== Level 3 with _emphasis_
^^^^^^^^^^^^^^^^^^^^^^^
Level 4 ===== Level 4
+++++++
Level 5 ====== Level 5
Level 1 == Level 1
-------
Level 2 with _emphasis_ === Level 2 with _emphasis_
~~~~~~~~~~~~~~~~~~~~~~~
Level 3 ==== Level 3
^^^^^^^
with no blank line with no blank line
Level 2 === Level 2
~~~~~~~
with no blank line with no blank line
''''' '''''
Paragraphs == Paragraphs
----------
Heres a regular paragraph. Heres a regular paragraph.
@ -56,8 +46,7 @@ here.
''''' '''''
Block Quotes == Block Quotes
------------
E-mail style: E-mail style:
@ -99,8 +88,7 @@ And a following paragraph.
''''' '''''
Code Blocks == Code Blocks
-----------
Code: Code:
@ -124,11 +112,9 @@ These should not be escaped: \$ \\ \> \[ \{
''''' '''''
Lists == Lists
-----
Unordered === Unordered
~~~~~~~~~
Asterisks tight: Asterisks tight:
@ -166,8 +152,7 @@ Minuses loose:
* Minus 2 * Minus 2
* Minus 3 * Minus 3
Ordered === Ordered
~~~~~~~
Tight: Tight:
@ -201,8 +186,7 @@ Item 1. graf two. The quick brown fox jumped over the lazy dogs back.
2. Item 2. 2. Item 2.
3. Item 3. 3. Item 3.
Nested === Nested
~~~~~~
* Tab * Tab
** Tab ** Tab
@ -226,16 +210,14 @@ Same thing but with paragraphs:
* Foe * Foe
3. Third 3. Third
Tabs and spaces === Tabs and spaces
~~~~~~~~~~~~~~~
* this is a list item indented with tabs * this is a list item indented with tabs
* this is a list item indented with spaces * 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 tabs
** this is an example list item indented with spaces ** this is an example list item indented with spaces
Fancy list markers === Fancy list markers
~~~~~~~~~~~~~~~~~~
1. begins with 2 1. begins with 2
2. and now 3 2. and now 3
@ -267,8 +249,7 @@ B. Williams
''''' '''''
Definition Lists == Definition Lists
----------------
Tight using spaces: Tight using spaces:
@ -348,8 +329,7 @@ orange::
1. sublist 1. sublist
2. sublist 2. sublist
HTML Blocks == HTML Blocks
-----------
Simple block on one line: Simple block on one line:
@ -411,8 +391,7 @@ Hrs:
''''' '''''
Inline Markup == Inline Markup
-------------
This is _emphasized_, and so _is this_. This is _emphasized_, and so _is this_.
@ -441,8 +420,7 @@ spaces: a^b c^d, a~b c~d.
''''' '''''
Smart quotes, ellipses, dashes == Smart quotes, ellipses, dashes
------------------------------
``Hello,'' said the spider. ```Shelob' is my name.'' ``Hello,'' said the spider. ```Shelob' is my name.''
@ -463,8 +441,7 @@ Ellipses…and…and….
''''' '''''
LaTeX == LaTeX
-----
* *
* latexmath:[$2+2=4$] * latexmath:[$2+2=4$]
@ -489,8 +466,7 @@ Heres a LaTeX table:
''''' '''''
Special Characters == Special Characters
------------------
Here is some unicode: Here is some unicode:
@ -544,11 +520,9 @@ Minus: -
''''' '''''
Links == Links
-----
Explicit === Explicit
~~~~~~~~
Just a link:/url/[URL]. Just a link:/url/[URL].
@ -568,8 +542,7 @@ mailto:nobody@nowhere.net[Email link]
link:[Empty]. link:[Empty].
Reference === Reference
~~~~~~~~~
Foo link:/url/[bar]. Foo link:/url/[bar].
@ -593,8 +566,7 @@ Foo link:/url/[bar].
Foo link:/url/[biz]. Foo link:/url/[biz].
With ampersands === With ampersands
~~~~~~~~~~~~~~~
Heres a http://example.com/?foo=1&bar=2[link with an ampersand in the URL]. Heres a http://example.com/?foo=1&bar=2[link with an ampersand in the URL].
@ -604,8 +576,7 @@ Heres an link:/script?foo=1&bar=2[inline link].
Heres an link:/script?foo=1&bar=2[inline link in pointy braces]. Heres an link:/script?foo=1&bar=2[inline link in pointy braces].
Autolinks === Autolinks
~~~~~~~~~
With an ampersand: http://example.com/?foo=1&bar=2 With an ampersand: http://example.com/?foo=1&bar=2
@ -627,8 +598,7 @@ or here: <http://example.com/>
''''' '''''
Images == Images
------
From ``Voyage dans la Lune'' by Georges Melies (1902): From ``Voyage dans la Lune'' by Georges Melies (1902):
@ -638,8 +608,7 @@ Here is a movie image:movie.jpg[movie] icon.
''''' '''''
Footnotes == Footnotes
---------
Here is a footnote reference,footnote:[Here is the footnote. It can go Here is a footnote reference,footnote:[Here is the footnote. It can go
anywhere after the footnote reference. It need not be placed at the end of the anywhere after the footnote reference. It need not be placed at the end of the