From db44ddfbde16d8aff0d62550014ac72b684b3eef Mon Sep 17 00:00:00 2001
From: Alexander Krotov <ilabdsf@gmail.com>
Date: Sat, 1 Sep 2018 16:14:06 +0300
Subject: Muse writer: wrap conditionalEscapeString result into "Muse" type

This removes the need to pass envInsideLinkDescription to it.
---
 src/Text/Pandoc/Writers/Muse.hs | 50 +++++++++++++++++++++++------------------
 1 file changed, 28 insertions(+), 22 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index 7f3b64ea7..beb289d02 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -322,20 +322,26 @@ containsFootnotes = p
         s [] = False
 
 -- | Return True if string should be escaped with <verbatim> tags
-shouldEscapeString :: Bool -> String -> Bool
-shouldEscapeString isInsideLinkDescription s =
-  any (`elem` ("#*<=|" :: String)) s ||
-  "::" `isInfixOf` s ||
-  "~~" `isInfixOf` s ||
-  "[[" `isInfixOf` s ||
-  ("]" `isInfixOf` s && isInsideLinkDescription) ||
-  containsFootnotes s
-
-conditionalEscapeString :: Bool -> String -> String
-conditionalEscapeString isInsideLinkDescription s =
-  if shouldEscapeString isInsideLinkDescription s
-    then escapeString s
-    else s
+shouldEscapeString :: PandocMonad m
+                   => String
+                   -> Muse m Bool
+shouldEscapeString s = do
+  insideLink <- asks envInsideLinkDescription
+  return $ any (`elem` ("#*<=|" :: String)) s ||
+           "::" `isInfixOf` s ||
+           "~~" `isInfixOf` s ||
+           "[[" `isInfixOf` s ||
+           ("]" `isInfixOf` s && insideLink) ||
+           containsFootnotes s
+
+conditionalEscapeString :: PandocMonad m
+                        => String
+                        -> Muse m String
+conditionalEscapeString s = do
+  shouldEscape <- shouldEscapeString s
+  if shouldEscape
+    then return $ escapeString s
+    else return $ s
 
 -- Expand Math and Cite before normalizing inline list
 preprocessInlineList :: PandocMonad m
@@ -459,9 +465,8 @@ inlineListToMuse' lst = do
 inlineToMuse :: PandocMonad m
              => Inline
              -> Muse m Doc
-inlineToMuse (Str str) = do
-  insideLink <- asks envInsideLinkDescription
-  return $ text $ conditionalEscapeString insideLink str
+inlineToMuse (Str str) =
+  text <$> conditionalEscapeString str
 inlineToMuse (Emph lst) = do
   contents <- inlineListToMuse lst
   return $ "<em>" <> contents <> "</em>"
@@ -516,11 +521,12 @@ inlineToMuse (Image attr alt (source,'f':'i':'g':':':title)) =
 inlineToMuse (Image attr@(_, classes, _) inlines (source, title)) = do
   opts <- asks envOptions
   alt <- local (\env -> env { envInsideLinkDescription = True }) $ inlineListToMuse inlines
-  let title' = if null title
-                  then if null inlines
-                          then ""
-                          else "[" <> alt <> "]"
-                  else "[" <> text (conditionalEscapeString True title) <> "]"
+  title' <- if null title
+            then if null inlines
+                 then return ""
+                 else return $ "[" <> alt <> "]"
+            else do s <- local (\env -> env { envInsideLinkDescription = True }) $ conditionalEscapeString title
+                    return $ "[" <> text s <> "]"
   let width = case dimension Width attr of
                 Just (Percent x) | isEnabled Ext_amuse opts -> " " ++ show (round x :: Integer)
                 _ -> ""
-- 
cgit v1.2.3