diff options
author | John MacFarlane <jgm@berkeley.edu> | 2021-05-19 16:14:49 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-05-19 16:14:49 -0700 |
commit | 5736b331d8ecaa12cc3e2712211ada37c665a93a (patch) | |
tree | 3322a4c5f853407f15c719ff10f060f56d6cd5e9 /src/Text/Pandoc/Readers | |
parent | 7efb71f4f6feae5c57e685b588e725b1ab27c4b5 (diff) | |
download | pandoc-5736b331d8ecaa12cc3e2712211ada37c665a93a.tar.gz |
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.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Parsing.hs | 21 |
2 files changed, 19 insertions, 14 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 |