aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Writers/Muse.hs45
-rw-r--r--test/Tests/Writers/Muse.hs3
-rw-r--r--test/writer.muse12
3 files changed, 43 insertions, 17 deletions
diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index 44224122e..eaae43604 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -67,11 +67,12 @@ type Notes = [[Block]]
type Muse m = ReaderT WriterEnv (StateT WriterState m)
data WriterEnv =
- WriterEnv { envOptions :: WriterOptions
- , envTopLevel :: Bool
+ WriterEnv { envOptions :: WriterOptions
+ , envTopLevel :: Bool
, envInsideBlock :: Bool
, envInlineStart :: Bool
- , envAfterSpace :: Bool
+ , envInsideLinkDescription :: Bool -- Escape ] if True
+ , envAfterSpace :: Bool
}
data WriterState =
@@ -98,6 +99,7 @@ writeMuse opts document =
, envTopLevel = True
, envInsideBlock = False
, envInlineStart = True
+ , envInsideLinkDescription = False
, envAfterSpace = True
}
@@ -304,12 +306,31 @@ startsWithMarker f (x:xs) =
startsWithMarker _ [] = False
-- | Escape special characters for Muse if needed.
-conditionalEscapeString :: String -> String
-conditionalEscapeString s =
- if any (`elem` ("#*<=>[]|" :: String)) s ||
+containsFootnotes :: String -> Bool
+containsFootnotes st =
+ p st
+ where p ('[':xs) = q xs || p xs
+ p (_:xs) = p xs
+ p "" = False
+ q (x:xs)
+ | (x `elem` ("123456789"::String)) = r xs || p xs
+ | otherwise = p xs
+ q [] = False
+ r ('0':xs) = r xs || p xs
+ r (xs) = s xs || q xs || p xs
+ s (']':_) = True
+ s (_:xs) = p xs
+ s [] = False
+
+conditionalEscapeString :: Bool -> String -> String
+conditionalEscapeString isInsideLinkDescription s =
+ if any (`elem` ("#*<=>|" :: String)) s ||
"::" `isInfixOf` s ||
"----" `isInfixOf` s ||
- "~~" `isInfixOf` s
+ "~~" `isInfixOf` s ||
+ "[[" `isInfixOf` s ||
+ ("]" `isInfixOf` s && isInsideLinkDescription) ||
+ containsFootnotes s
then escapeString s
else s
@@ -428,7 +449,9 @@ inlineListToMuse = inlineListToMuse'' False
inlineToMuse :: PandocMonad m
=> Inline
-> Muse m Doc
-inlineToMuse (Str str) = return $ text $ conditionalEscapeString str
+inlineToMuse (Str str) = do
+ insideLink <- asks envInsideLinkDescription
+ return $ text $ conditionalEscapeString insideLink str
inlineToMuse (Emph lst) = do
contents <- inlineListToMuse lst
return $ "<em>" <> contents <> "</em>"
@@ -469,7 +492,7 @@ inlineToMuse (Link _ txt (src, _)) =
case txt of
[Str x] | escapeURI x == src ->
return $ "[[" <> text (escapeLink x) <> "]]"
- _ -> do contents <- inlineListToMuse txt
+ _ -> do contents <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse txt
return $ "[[" <> text (escapeLink src) <> "][" <> contents <> "]]"
where escapeLink lnk = if isImageUrl lnk then "URL:" ++ urlEscapeBrackets lnk else urlEscapeBrackets lnk
-- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el
@@ -479,7 +502,7 @@ inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) =
inlineToMuse (Image attr alt (source,title))
inlineToMuse (Image attr inlines (source, title)) = do
opts <- asks envOptions
- alt <- inlineListToMuse inlines
+ alt <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse inlines
let title' = if null title
then if null inlines
then ""
@@ -489,7 +512,7 @@ inlineToMuse (Image attr inlines (source, title)) = do
Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer)
_ -> ""
return $ "[[" <> text (urlEscapeBrackets source ++ width) <> "]" <> title' <> "]"
- where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString s
+ where escape s = if "]" `isInfixOf` s then escapeString s else conditionalEscapeString True s
inlineToMuse (Note contents) = do
-- add to notes in state
notes <- gets stNotes
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index 88d2db8cf..eca7ed736 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -301,8 +301,11 @@ tests = [ testGroup "block elements"
[ testGroup "string"
[ "string" =: str "foo" =?> "foo"
, "escape footnote" =: str "[1]" =?> "<verbatim>[1]</verbatim>"
+ , "do not escape brackets" =: str "[12ab]" =?> "[12ab]"
, "escape verbatim close tag" =: str "foo</verbatim>bar"
=?> "<verbatim>foo<</verbatim><verbatim>/verbatim>bar</verbatim>"
+ , "escape link-like text" =: str "[[https://www.example.org]]"
+ =?> "<verbatim>[[https://www.example.org]]</verbatim>"
, "escape pipe to avoid accidental tables" =: str "foo | bar"
=?> "<verbatim>foo | bar</verbatim>"
, "escape hash to avoid accidental anchors" =: text "#foo bar"
diff --git a/test/writer.muse b/test/writer.muse
index c534b63b3..83a53a1ab 100644
--- a/test/writer.muse
+++ b/test/writer.muse
@@ -576,9 +576,9 @@ Left brace: {
Right brace: }
-Left bracket: <verbatim>[</verbatim>
+Left bracket: [
-Right bracket: <verbatim>]</verbatim>
+Right bracket: ]
Left paren: (
@@ -634,7 +634,7 @@ Indented [[/url][twice]].
Indented [[/url][thrice]].
-This should <verbatim>[not][]</verbatim> be a link.
+This should [not][] be a link.
<example>
[not]: /url
@@ -690,8 +690,8 @@ Here is a movie [[movie.jpg][movie]] icon.
* Footnotes
Here is a footnote reference,[1] and another.[2] This should <em>not</em> be a
-footnote reference, because it contains a <verbatim>space.[^my</verbatim>
-<verbatim>note]</verbatim> Here is an inline note.[3]
+footnote reference, because it contains a space.[^my note] Here is an inline
+note.[3]
<quote>
Notes can go in quotes.[4]
@@ -718,7 +718,7 @@ This paragraph should not be part of the note, as it is not indented.
[3] This is <em>easier</em> to type. Inline notes may contain
[[http://google.com][links]] and <code>]</code> verbatim characters, as
- well as <verbatim>[bracketed</verbatim> <verbatim>text].</verbatim>
+ well as [bracketed text].
[4] In quote.