Roff reader: use escapeArg in macroArg.

This commit is contained in:
John MacFarlane 2018-10-28 20:41:17 -07:00
parent b1e7101393
commit 6b8e595e72

View file

@ -53,7 +53,7 @@ import Control.Monad (void, mzero, guard, when, mplus)
import Control.Monad.Except (throwError) import Control.Monad.Except (throwError)
import Text.Pandoc.Class import Text.Pandoc.Class
(getResourcePath, readFileFromDirs, PandocMonad(..), report) (getResourcePath, readFileFromDirs, PandocMonad(..), report)
import Data.Char (isLower, toLower, toUpper, chr, ord, import Data.Char (isLower, toLower, toUpper, chr,
isAscii, isAlphaNum, isSpace) isAscii, isAlphaNum, isSpace)
import Data.Default (Default) import Data.Default (Default)
import qualified Data.Map as M import qualified Data.Map as M
@ -602,9 +602,14 @@ linePart = macroArg <|> escape <|>
macroArg :: PandocMonad m => RoffLexer m [LinePart] macroArg :: PandocMonad m => RoffLexer m [LinePart]
macroArg = try $ do macroArg = try $ do
pos <- getPosition
string "\\\\$" string "\\\\$"
x <- digit x <- escapeArg <|> count 1 digit
return [MacroArg $ ord x - ord '0'] case safeRead x of
Just i -> return [MacroArg i]
Nothing -> do
report $ SkippedContent ("illegal macro argument " ++ x) pos
return []
regularText :: PandocMonad m => RoffLexer m [LinePart] regularText :: PandocMonad m => RoffLexer m [LinePart]
regularText = do regularText = do