parent
0267c1f6f3
commit
c1b51b1282
2 changed files with 31 additions and 27 deletions
|
@ -21,7 +21,7 @@ module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where
|
||||||
import Prelude
|
import Prelude
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Control.Monad.State.Strict
|
import Control.Monad.State.Strict
|
||||||
import Data.Char (isSpace, isAlphaNum)
|
import Data.Char (isAlphaNum)
|
||||||
import Data.Default
|
import Data.Default
|
||||||
import Data.List (find, intersperse, sortBy, transpose)
|
import Data.List (find, intersperse, sortBy, transpose)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -346,13 +346,13 @@ linkAttributes opts attr =
|
||||||
else empty
|
else empty
|
||||||
|
|
||||||
-- | Ordered list start parser for use in Para below.
|
-- | Ordered list start parser for use in Para below.
|
||||||
olMarker :: Parser Text ParserState Char
|
olMarker :: Parser Text ParserState ()
|
||||||
olMarker = do (start, style', delim) <- anyOrderedListMarker
|
olMarker = do (start, style', delim) <- anyOrderedListMarker
|
||||||
if delim == Period &&
|
if delim == Period &&
|
||||||
(style' == UpperAlpha || (style' == UpperRoman &&
|
(style' == UpperAlpha || (style' == UpperRoman &&
|
||||||
start `elem` [1, 5, 10, 50, 100, 500, 1000]))
|
start `elem` [1, 5, 10, 50, 100, 500, 1000]))
|
||||||
then spaceChar >> spaceChar
|
then mzero -- it needs 2 spaces anyway
|
||||||
else spaceChar
|
else eof
|
||||||
|
|
||||||
-- | True if string begins with an ordered list marker
|
-- | True if string begins with an ordered list marker
|
||||||
beginsWithOrderedListMarker :: Text -> Bool
|
beginsWithOrderedListMarker :: Text -> Bool
|
||||||
|
@ -419,34 +419,32 @@ blockToMarkdown' opts (Div attrs ils) = do
|
||||||
where (id',classes',kvs') = attrs
|
where (id',classes',kvs') = attrs
|
||||||
attrs' = (id',classes',("markdown","1"):kvs')
|
attrs' = (id',classes',("markdown","1"):kvs')
|
||||||
blockToMarkdown' opts (Plain inlines) = do
|
blockToMarkdown' opts (Plain inlines) = do
|
||||||
contents <- inlineListToMarkdown opts inlines
|
|
||||||
-- escape if para starts with ordered list marker
|
-- escape if para starts with ordered list marker
|
||||||
isPlain <- asks envPlain
|
isPlain <- asks envPlain
|
||||||
let colwidth = if writerWrapText opts == WrapAuto
|
|
||||||
then Just $ writerColumns opts
|
|
||||||
else Nothing
|
|
||||||
let rendered = render colwidth contents
|
|
||||||
let escapeMarker = T.concatMap $ \x -> if x `elemText` ".()"
|
let escapeMarker = T.concatMap $ \x -> if x `elemText` ".()"
|
||||||
then T.pack ['\\', x]
|
then T.pack ['\\', x]
|
||||||
else T.singleton x
|
else T.singleton x
|
||||||
let spaceOrNothing = (not isPlain &&) . maybe True (isSpace . fst) . T.uncons
|
let startsWithSpace (Space:_) = True
|
||||||
let contents' =
|
startsWithSpace (SoftBreak:_) = True
|
||||||
case T.uncons rendered of
|
startsWithSpace _ = False
|
||||||
Just ('%', _)
|
let inlines' =
|
||||||
| isEnabled Ext_pandoc_title_block opts &&
|
if isPlain
|
||||||
isEnabled Ext_all_symbols_escapable opts -> "\\" <> contents
|
then inlines
|
||||||
Just ('+', s) | spaceOrNothing s -> "\\" <> contents
|
else case inlines of
|
||||||
Just ('*', s) | spaceOrNothing s -> "\\" <> contents
|
(Str t:ys)
|
||||||
Just ('-', s) | spaceOrNothing s -> "\\" <> contents
|
| not isPlain
|
||||||
Just ('|', _) | (isEnabled Ext_line_blocks opts ||
|
, (null ys || startsWithSpace ys)
|
||||||
isEnabled Ext_pipe_tables opts)
|
, beginsWithOrderedListMarker t
|
||||||
&& isEnabled Ext_all_symbols_escapable opts
|
-> RawInline (Format "markdown") (escapeMarker t):ys
|
||||||
-> "\\" <> contents
|
(Str t:_)
|
||||||
_ | not isPlain && beginsWithOrderedListMarker rendered
|
| not isPlain
|
||||||
&& isEnabled Ext_all_symbols_escapable opts
|
, t == "+" || t == "-" ||
|
||||||
-> literal $ escapeMarker rendered
|
(t == "%" && isEnabled Ext_pandoc_title_block opts &&
|
||||||
| otherwise -> contents
|
isEnabled Ext_all_symbols_escapable opts)
|
||||||
return $ contents' <> cr
|
-> RawInline (Format "markdown") "\\" : inlines
|
||||||
|
_ -> inlines
|
||||||
|
contents <- inlineListToMarkdown opts inlines'
|
||||||
|
return $ contents <> cr
|
||||||
-- title beginning with fig: indicates figure
|
-- title beginning with fig: indicates figure
|
||||||
blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Just tit))])
|
blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Just tit))])
|
||||||
| isEnabled Ext_raw_html opts &&
|
| isEnabled Ext_raw_html opts &&
|
||||||
|
|
6
test/command/5918.md
Normal file
6
test/command/5918.md
Normal file
|
@ -0,0 +1,6 @@
|
||||||
|
```
|
||||||
|
% pandoc -t markdown -f latex
|
||||||
|
1. \textsc{excessive}
|
||||||
|
^D
|
||||||
|
1\. [excessive]{.smallcaps}
|
||||||
|
```
|
Loading…
Add table
Reference in a new issue