aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs12
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs21
-rw-r--r--test/command/4442.md2
-rw-r--r--test/command/7299.md23
4 files changed, 43 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index f90d562ae..2ace18d1b 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -232,16 +232,6 @@ mkImage options (T.unpack -> src) = do
_ -> return src
return $ imageWith attr (T.pack src') "" alt
-doxspace :: PandocMonad m => LP m Inlines
-doxspace =
- (space <$ lookAhead (satisfyTok startsWithLetter)) <|> return mempty
- where startsWithLetter (Tok _ Word t) =
- case T.uncons t of
- Just (c, _) | isLetter c -> True
- _ -> False
- startsWithLetter _ = False
-
-
removeDoubleQuotes :: Text -> Text
removeDoubleQuotes t =
Data.Maybe.fromMaybe t $ T.stripPrefix "\"" t >>= T.stripSuffix "\""
@@ -417,8 +407,6 @@ inlineCommands = M.unions
-- LaTeX colors
, ("textcolor", coloredInline "color")
, ("colorbox", coloredInline "background-color")
- -- xspace
- , ("xspace", doxspace)
-- etoolbox
, ("ifstrequal", ifstrequal)
, ("newtoggle", braced >>= newToggle)
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 35ce3509d..b6804a825 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -464,7 +464,7 @@ satisfyTok f = do
doMacros :: PandocMonad m => LP m ()
doMacros = do
st <- getState
- unless (sVerbatimMode st || M.null (sMacros st)) $ do
+ unless (sVerbatimMode st) $
getInput >>= doMacros' 1 >>= setInput
doMacros' :: PandocMonad m => Int -> [Tok] -> LP m [Tok]
@@ -526,7 +526,7 @@ doMacros' n inp =
$ throwError $ PandocMacroLoop name
macros <- sMacros <$> getState
case M.lookup name macros of
- Nothing -> mzero
+ Nothing -> trySpecialMacro name ts
Just (Macro expansionPoint argspecs optarg newtoks) -> do
let getargs' = do
args <-
@@ -554,6 +554,23 @@ doMacros' n inp =
ExpandWhenUsed -> doMacros' (n' + 1) result
ExpandWhenDefined -> return result
+-- | Certain macros do low-level tex manipulations that can't
+-- be represented in our Macro type, so we handle them here.
+trySpecialMacro :: PandocMonad m => Text -> [Tok] -> LP m [Tok]
+trySpecialMacro "xspace" ts = do
+ ts' <- doMacros' 1 ts
+ case ts' of
+ Tok pos Word t : _
+ | startsWithAlphaNum t -> return $ Tok pos Spaces " " : ts'
+ _ -> return ts'
+trySpecialMacro _ _ = mzero
+
+startsWithAlphaNum :: Text -> Bool
+startsWithAlphaNum t =
+ case T.uncons t of
+ Just (c, _) | isAlphaNum c -> True
+ _ -> False
+
setpos :: SourcePos -> Tok -> Tok
setpos spos (Tok _ tt txt) = Tok spos tt txt
diff --git a/test/command/4442.md b/test/command/4442.md
index 8574fe759..447073406 100644
--- a/test/command/4442.md
+++ b/test/command/4442.md
@@ -5,5 +5,5 @@
^D
\newcommand{\myFruit}{Mango\xspace}
-Mango\xspace is the king of fruits.
+Mango is the king of fruits.
```
diff --git a/test/command/7299.md b/test/command/7299.md
new file mode 100644
index 000000000..0847c40ce
--- /dev/null
+++ b/test/command/7299.md
@@ -0,0 +1,23 @@
+```
+% pandoc -f latex -t plain
+$1-{\ensuremath{r}\xspace}$
+^D
+1 − r
+```
+
+```
+% pandoc -f latex -t plain
+\newcommand{\foo}{Foo\xspace}
+
+$\text{\foo bar}$
+^D
+Foo bar
+```
+
+```
+% pandoc -f latex -t plain
+a\xspace b
+^D
+a b
+```
+