Roff tokenizer: check for first-column before parsing macro.
Also add SourcePos as argument to lexRoff, so we can pass in current source pos when parsing a table cell. Closes #5025.
This commit is contained in:
parent
a3b351c3a6
commit
f5e26e4512
2 changed files with 10 additions and 6 deletions
|
@ -52,7 +52,7 @@ import Text.Pandoc.Shared (crFilter)
|
|||
import Text.Pandoc.Readers.Roff -- TODO explicit imports
|
||||
import Text.Parsec hiding (tokenPrim)
|
||||
import qualified Text.Parsec as Parsec
|
||||
import Text.Parsec.Pos (updatePosString)
|
||||
import Text.Parsec.Pos (updatePosString, initialPos)
|
||||
import qualified Data.Foldable as Foldable
|
||||
|
||||
data ManState = ManState { readerOptions :: ReaderOptions
|
||||
|
@ -69,7 +69,7 @@ type ManParser m = ParserT [RoffToken] ManState m
|
|||
-- | Read man (troff) from an input string and return a Pandoc document.
|
||||
readMan :: PandocMonad m => ReaderOptions -> T.Text -> m Pandoc
|
||||
readMan opts txt = do
|
||||
tokenz <- lexRoff (crFilter txt)
|
||||
tokenz <- lexRoff (initialPos "input") (crFilter txt)
|
||||
let state = def {readerOptions = opts} :: ManState
|
||||
eitherdoc <- readWithMTokens parseMan state
|
||||
(Foldable.toList . unRoffTokens $ tokenz)
|
||||
|
|
|
@ -311,6 +311,7 @@ lexComment = do
|
|||
lexMacro :: PandocMonad m => RoffLexer m RoffTokens
|
||||
lexMacro = do
|
||||
pos <- getPosition
|
||||
guard $ sourceColumn pos == 1
|
||||
char '.' <|> char '\''
|
||||
skipMany spacetab
|
||||
macroName <- many (satisfy (not . isSpace))
|
||||
|
@ -369,7 +370,9 @@ lexTableRows = do
|
|||
return $ zip aligns rows
|
||||
|
||||
tableCell :: PandocMonad m => RoffLexer m RoffTokens
|
||||
tableCell = (enclosedCell <|> simpleCell) >>= lexRoff . T.pack
|
||||
tableCell = do
|
||||
pos <- getPosition
|
||||
(enclosedCell <|> simpleCell) >>= lexRoff pos . T.pack
|
||||
where
|
||||
enclosedCell = do
|
||||
try (string "T{")
|
||||
|
@ -642,9 +645,10 @@ linePartsToString = mconcat . map go
|
|||
go _ = mempty
|
||||
|
||||
-- | Tokenize a string as a sequence of groff tokens.
|
||||
lexRoff :: PandocMonad m => T.Text -> m RoffTokens
|
||||
lexRoff txt = do
|
||||
eithertokens <- readWithM (mconcat <$> many manToken) def (T.unpack txt)
|
||||
lexRoff :: PandocMonad m => SourcePos -> T.Text -> m RoffTokens
|
||||
lexRoff pos txt = do
|
||||
eithertokens <- readWithM (do setPosition pos
|
||||
mconcat <$> many manToken) def (T.unpack txt)
|
||||
case eithertokens of
|
||||
Left e -> throwError e
|
||||
Right tokenz -> return tokenz
|
||||
|
|
Loading…
Add table
Reference in a new issue