From da5e9e5956aae3ac83edef7831939553360b8964 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Wed, 3 Mar 2021 11:22:42 -0800
Subject: [PATCH] Move enquote commands to T.P.LaTeX.Lang.

---
 src/Text/Pandoc/Readers/LaTeX.hs        | 22 ++--------------
 src/Text/Pandoc/Readers/LaTeX/Inline.hs |  2 --
 src/Text/Pandoc/Readers/LaTeX/Lang.hs   | 34 +++++++++++++++++++++++--
 3 files changed, 34 insertions(+), 24 deletions(-)

diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 4ec038b94..a4261bbeb 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -59,6 +59,7 @@ import Text.Pandoc.Readers.LaTeX.Math (dollarsMath, inlineEnvironments,
 import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments)
 import Text.Pandoc.Readers.LaTeX.Macro (macroDef)
 import Text.Pandoc.Readers.LaTeX.Lang (inlineLanguageCommands,
+                                       enquoteCommands,
                                        babelLangToBCP47, setDefaultLanguage)
 import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands)
 import Text.Pandoc.Readers.LaTeX.Inline (acronymCommands, refCommands,
@@ -293,18 +294,6 @@ quoted' f starter ender = do
 lit :: Text -> LP m Inlines
 lit = pure . str
 
-enquote :: PandocMonad m => Bool -> Maybe Text -> LP m Inlines
-enquote starred mblang = do
-  skipopts
-  let lang = mblang >>= babelLangToBCP47
-  let langspan = case lang of
-                      Nothing -> id
-                      Just l  -> spanWith ("",[],[("lang", renderLang l)])
-  quoteContext <- sQuoteContext <$> getState
-  if starred || quoteContext == InDoubleQuote
-     then singleQuoted . langspan <$> withQuoteContext InSingleQuote tok
-     else doubleQuoted . langspan <$> withQuoteContext InDoubleQuote tok
-
 blockquote :: PandocMonad m => Bool -> Maybe Text -> LP m Blocks
 blockquote cvariant mblang = do
   citepar <- if cvariant
@@ -359,6 +348,7 @@ inlineCommands = M.unions
   , nameCommands
   , verbCommands
   , charCommands
+  , enquoteCommands tok
   , inlineLanguageCommands tok
   , biblatexInlineCommands tok
   , rest ]
@@ -418,14 +408,6 @@ inlineCommands = M.unions
                              src <- braced
                              mkImage options . unescapeURL . removeDoubleQuotes $
                                  untokenize src)
-    , ("enquote*", enquote True Nothing)
-    , ("enquote", enquote False Nothing)
-    -- foreignquote is supposed to use native quote marks
-    , ("foreignquote*", braced >>= enquote True . Just . untokenize)
-    , ("foreignquote", braced >>= enquote False . Just . untokenize)
-    -- hypehnquote uses regular quotes
-    , ("hyphenquote*", braced >>= enquote True . Just . untokenize)
-    , ("hyphenquote", braced >>= enquote False . Just . untokenize)
     , ("hyperlink", hyperlink)
     , ("hypertarget", hypertargetInline)
     -- hyphenat
diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
index 37c29188e..8bdff58f7 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
@@ -155,8 +155,6 @@ romanNumeralArg = spaces *> (parser <|> inBraces)
         Prelude.fail "Non-digits in argument to \\Rn or \\RN"
       safeRead digits
 
-
-
 verbCommands :: PandocMonad m => M.Map Text (LP m Inlines)
 verbCommands = M.fromList
   [ ("verb", doverb)
diff --git a/src/Text/Pandoc/Readers/LaTeX/Lang.hs b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
index 24acbdbe4..08e217bdb 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Lang.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Lang.hs
@@ -15,6 +15,7 @@ module Text.Pandoc.Readers.LaTeX.Lang
   ( setDefaultLanguage
   , polyglossiaLangToBCP47
   , babelLangToBCP47
+  , enquoteCommands
   , inlineLanguageCommands
   )
 where
@@ -25,8 +26,37 @@ import Text.Pandoc.Shared (extractSpaces)
 import Text.Pandoc.BCP47 (Lang(..), renderLang)
 import Text.Pandoc.Class (PandocMonad(..), setTranslations)
 import Text.Pandoc.Readers.LaTeX.Parsing
-import Text.Pandoc.Parsing (updateState, option)
-import Text.Pandoc.Builder (Blocks, Inlines, setMeta, str, spanWith)
+import Text.Pandoc.Parsing (updateState, option, getState, QuoteContext(..),
+                            withQuoteContext)
+import Text.Pandoc.Builder (Blocks, Inlines, setMeta, str, spanWith,
+                            singleQuoted, doubleQuoted)
+
+enquote :: PandocMonad m
+        => LP m Inlines
+        -> Bool -> Maybe Text -> LP m Inlines
+enquote tok starred mblang = do
+  skipopts
+  let lang = mblang >>= babelLangToBCP47
+  let langspan = case lang of
+                      Nothing -> id
+                      Just l  -> spanWith ("",[],[("lang", renderLang l)])
+  quoteContext <- sQuoteContext <$> getState
+  if starred || quoteContext == InDoubleQuote
+     then singleQuoted . langspan <$> withQuoteContext InSingleQuote tok
+     else doubleQuoted . langspan <$> withQuoteContext InDoubleQuote tok
+
+enquoteCommands :: PandocMonad m
+                => LP m Inlines -> M.Map Text (LP m Inlines)
+enquoteCommands tok = M.fromList
+  [ ("enquote*", enquote tok True Nothing)
+  , ("enquote", enquote tok False Nothing)
+  -- foreignquote is supposed to use native quote marks
+  , ("foreignquote*", braced >>= enquote tok True . Just . untokenize)
+  , ("foreignquote", braced >>= enquote tok False . Just . untokenize)
+  -- hypehnquote uses regular quotes
+  , ("hyphenquote*", braced >>= enquote tok True . Just . untokenize)
+  , ("hyphenquote", braced >>= enquote tok False . Just . untokenize)
+  ]
 
 foreignlanguage :: PandocMonad m => LP m Inlines -> LP m Inlines
 foreignlanguage tok = do