LaTeX reader: better support for \xspace.

Previously we only supported it in inline contexts; now
we support it in all contexts, including math.

Partially addresses #7299.
This commit is contained in:
John MacFarlane 2021-05-19 16:14:49 -07:00
parent 7efb71f4f6
commit 5736b331d8
4 changed files with 43 additions and 15 deletions

View file

@ -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)

View file

@ -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

View file

@ -5,5 +5,5 @@
^D
\newcommand{\myFruit}{Mango\xspace}
Mango\xspace is the king of fruits.
Mango is the king of fruits.
```

23
test/command/7299.md Normal file
View file

@ -0,0 +1,23 @@
```
% pandoc -f latex -t plain
$1-{\ensuremath{r}\xspace}$
^D
1r
```
```
% 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
```