asciidoc writer: translate numberLines attribute to linesnum switch
AsciiDoctor allows to request line numbering on code blocks by using a switch on the `source` block, such as in: ``` [source%linesnum,haskell] ---- some Haskell code here ---- ```
This commit is contained in:
parent
628cde48cf
commit
a41c1fe0bb
2 changed files with 21 additions and 2 deletions
|
@ -21,7 +21,7 @@ AsciiDoc: <http://www.methods.co.nz/asciidoc/>
|
|||
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc, writeAsciiDoctor) where
|
||||
import Control.Monad.State.Strict
|
||||
import Data.Char (isPunctuation, isSpace)
|
||||
import Data.List (intercalate, intersperse)
|
||||
import Data.List (delete, intercalate, intersperse)
|
||||
import Data.List.NonEmpty (NonEmpty(..))
|
||||
import Data.Maybe (fromMaybe, isJust)
|
||||
import qualified Data.Set as Set
|
||||
|
@ -193,7 +193,10 @@ blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush (
|
|||
then "...." $$ literal str $$ "...."
|
||||
else attrs $$ "----" $$ literal str $$ "----")
|
||||
<> blankline
|
||||
where attrs = "[" <> literal (T.intercalate "," ("source" : classes)) <> "]"
|
||||
where attrs = "[" <> literal (T.intercalate "," classes') <> "]"
|
||||
classes' = if "numberLines" `elem` classes
|
||||
then "source%linesnum" : delete "numberLines" classes
|
||||
else "source" : classes
|
||||
blockToAsciiDoc opts (BlockQuote blocks) = do
|
||||
contents <- blockListToAsciiDoc opts blocks
|
||||
let isBlock (BlockQuote _) = True
|
||||
|
|
|
@ -38,6 +38,22 @@ tests = [ testGroup "emphasis"
|
|||
para (singleQuoted (strong (text "foo"))) =?>
|
||||
"`**foo**'"
|
||||
]
|
||||
, testGroup "blocks"
|
||||
[ testAsciidoc "code block without line numbers" $
|
||||
codeBlockWith ("", [ "haskell" ], []) "foo" =?> unlines
|
||||
[ "[source,haskell]"
|
||||
, "----"
|
||||
, "foo"
|
||||
, "----"
|
||||
]
|
||||
, testAsciidoc "code block with line numbers" $
|
||||
codeBlockWith ("", [ "haskell", "numberLines" ], []) "foo" =?> unlines
|
||||
[ "[source%linesnum,haskell]"
|
||||
, "----"
|
||||
, "foo"
|
||||
, "----"
|
||||
]
|
||||
]
|
||||
, testGroup "tables"
|
||||
[ testAsciidoc "empty cells" $
|
||||
simpleTable [] [[mempty],[mempty]] =?> unlines
|
||||
|
|
Loading…
Add table
Reference in a new issue