aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs5
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs11
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs29
3 files changed, 25 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 296c55f32..60d69638b 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -1126,7 +1126,10 @@ explicitLink = try $ do
skipSpaces
string "`_"
optional $ char '_' -- anonymous form
- return $ B.link (escapeURI $ trim src) "" label'
+ let label'' = if label' == mempty
+ then B.str src
+ else label'
+ return $ B.link (escapeURI $ trim src) "" label''
referenceLink :: RSTParser Inlines
referenceLink = try $ do
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 17c6583ff..3b8278e27 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -63,7 +63,7 @@ import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
import Text.HTML.TagSoup (parseTags, innerText, fromAttrib, Tag(..))
import Text.HTML.TagSoup.Match
import Data.List ( intercalate )
-import Data.Char ( digitToInt, isUpper)
+import Data.Char ( digitToInt, isUpper )
import Control.Monad ( guard, liftM, when )
import Text.Pandoc.Compat.Monoid ((<>))
import Text.Printf
@@ -540,8 +540,8 @@ image = try $ do
let attr = case lookup "style" kvs of
Just stls -> (ident, cls, pickStylesToKVs ["width", "height"] stls)
Nothing -> (ident, cls, kvs)
- src <- manyTill anyChar' (lookAhead $ oneOf "!(")
- alt <- option "" (try $ (char '(' >> manyTill anyChar' (char ')')))
+ src <- many1 (noneOf " \t\n\r!(")
+ alt <- option "" $ try $ char '(' *> manyTill anyChar (char ')')
char '!'
return $ B.imageWith attr src alt (B.str alt)
@@ -639,10 +639,7 @@ simpleInline :: Parser [Char] ParserState t -- ^ surrounding parser
-> (Inlines -> Inlines) -- ^ Inline constructor
-> Parser [Char] ParserState Inlines -- ^ content parser (to be used repeatedly)
simpleInline border construct = try $ do
- st <- getState
- pos <- getPosition
- let afterString = stateLastStrPos st == Just pos
- guard $ not afterString
+ notAfterString
border *> notFollowedBy (oneOf " \t\n\r")
attr <- attributes
body <- trimInlines . mconcat <$>
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 1ff8d2ab9..b04e33085 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -55,6 +55,7 @@ import qualified Data.HashMap.Strict as H
import qualified Data.Vector as V
import qualified Data.Text as T
import qualified Data.Set as Set
+import Network.HTTP ( urlEncode )
type Notes = [[Block]]
type Ref = ([Inline], Target, Attr)
@@ -856,18 +857,22 @@ inlineToMarkdown opts (Str str) = do
if stPlain st
then return $ text str
else return $ text $ escapeString opts str
-inlineToMarkdown opts (Math InlineMath str)
- | isEnabled Ext_tex_math_dollars opts =
- return $ "$" <> text str <> "$"
- | isEnabled Ext_tex_math_single_backslash opts =
- return $ "\\(" <> text str <> "\\)"
- | isEnabled Ext_tex_math_double_backslash opts =
- return $ "\\\\(" <> text str <> "\\\\)"
- | otherwise = do
- plain <- gets stPlain
- inlineListToMarkdown opts $
- (if plain then makeMathPlainer else id) $
- texMathToInlines InlineMath str
+inlineToMarkdown opts (Math InlineMath str) =
+ case writerHTMLMathMethod opts of
+ WebTeX url ->
+ inlineToMarkdown opts (Image nullAttr [Str str]
+ (url ++ urlEncode str, str))
+ _ | isEnabled Ext_tex_math_dollars opts ->
+ return $ "$" <> text str <> "$"
+ | isEnabled Ext_tex_math_single_backslash opts ->
+ return $ "\\(" <> text str <> "\\)"
+ | isEnabled Ext_tex_math_double_backslash opts ->
+ return $ "\\\\(" <> text str <> "\\\\)"
+ | otherwise -> do
+ plain <- gets stPlain
+ inlineListToMarkdown opts $
+ (if plain then makeMathPlainer else id) $
+ texMathToInlines InlineMath str
inlineToMarkdown opts (Math DisplayMath str)
| isEnabled Ext_tex_math_dollars opts =
return $ "$$" <> text str <> "$$"