Roff readers: better parsing of groups.

We now allow groups where the closing `\\}` isn't at the
beginning of a line.

Closes #5410.
This commit is contained in:
John MacFarlane 2019-09-04 09:24:42 -07:00
parent 0a3cc0be45
commit e4cca4cf67
3 changed files with 13 additions and 10 deletions

View file

@ -33,7 +33,7 @@ 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, import Data.Char (isLower, toLower, toUpper, chr,
isAscii, isAlphaNum, isSpace) isAscii, isAlphaNum)
import Data.Default (Default) import Data.Default (Default)
import qualified Data.Map as M import qualified Data.Map as M
import Data.List (intercalate) import Data.List (intercalate)
@ -130,7 +130,7 @@ type RoffLexer m = ParserT [Char] RoffState m
-- --
eofline :: Stream s m Char => ParsecT s u m () eofline :: Stream s m Char => ParsecT s u m ()
eofline = void newline <|> eof eofline = void newline <|> eof <|> () <$ lookAhead (string "\\}")
spacetab :: Stream s m Char => ParsecT s u m Char spacetab :: Stream s m Char => ParsecT s u m Char
spacetab = char ' ' <|> char '\t' spacetab = char ' ' <|> char '\t'
@ -144,7 +144,7 @@ combiningAccentsMap =
M.fromList $ map (\(x,y) -> (y,x)) combiningAccents M.fromList $ map (\(x,y) -> (y,x)) combiningAccents
escape :: PandocMonad m => RoffLexer m [LinePart] escape :: PandocMonad m => RoffLexer m [LinePart]
escape = do escape = try $ do
backslash backslash
escapeGlyph <|> escapeNormal escapeGlyph <|> escapeNormal
@ -193,7 +193,7 @@ readUnicodeChar _ = Nothing
escapeNormal :: PandocMonad m => RoffLexer m [LinePart] escapeNormal :: PandocMonad m => RoffLexer m [LinePart]
escapeNormal = do escapeNormal = do
c <- anyChar c <- noneOf "{}"
optional expandString optional expandString
case c of case c of
' ' -> return [RoffStr " "] ' ' -> return [RoffStr " "]
@ -256,9 +256,7 @@ escapeNormal = do
'w' -> escIgnore 'w' [quoteArg] 'w' -> escIgnore 'w' [quoteArg]
'x' -> escIgnore 'x' [quoteArg] 'x' -> escIgnore 'x' [quoteArg]
'z' -> escIgnore 'z' [count 1 anyChar] 'z' -> escIgnore 'z' [count 1 anyChar]
'{' -> return mempty
'|' -> return [RoffStr "\x2006"] --1/6 em space '|' -> return [RoffStr "\x2006"] --1/6 em space
'}' -> return mempty
'~' -> return [RoffStr "\160"] -- nonbreaking space '~' -> return [RoffStr "\160"] -- nonbreaking space
'\\' -> do '\\' -> do
mode <- roffMode <$> getState mode <- roffMode <$> getState
@ -350,7 +348,7 @@ lexMacro = do
guard $ sourceColumn pos == 1 || afterConditional st guard $ sourceColumn pos == 1 || afterConditional st
char '.' <|> char '\'' char '.' <|> char '\''
skipMany spacetab skipMany spacetab
macroName <- many (satisfy (not . isSpace)) macroName <- many (satisfy isAlphaNum)
case macroName of case macroName of
"nop" -> return mempty "nop" -> return mempty
"ie" -> lexConditional "ie" "ie" -> lexConditional "ie"
@ -361,8 +359,6 @@ lexMacro = do
args <- lexArgs args <- lexArgs
case macroName of case macroName of
"" -> return mempty "" -> return mempty
"\\\"" -> return mempty
"\\#" -> return mempty
"TS" -> lexTable pos "TS" -> lexTable pos
"de" -> lexMacroDef args "de" -> lexMacroDef args
"de1" -> lexMacroDef args "de1" -> lexMacroDef args

View file

@ -74,7 +74,7 @@ tests = [
=?> para (text "hi " <> emph (text "there " <> strong (text "bold")) <> =?> para (text "hi " <> emph (text "there " <> strong (text "bold")) <>
text " ok") text " ok")
, "skip" =: , "skip" =:
"a\\%\\{\\}\\\n\\:b\\0" "a\\%\\\n\\:b\\0"
=?> (para $ str "ab\8199") =?> (para $ str "ab\8199")
, "replace" =: , "replace" =:
"\\-\\ \\\\\\[lq]\\[rq]\\[em]\\[en]\\*(lq\\*(rq" "\\-\\ \\\\\\[lq]\\[rq]\\[em]\\[en]\\*(lq\\*(rq"

7
test/command/5410.md Normal file
View file

@ -0,0 +1,7 @@
```
% pandoc -f man -t native
.ie n \{\
'br\}
^D
[Para [LineBreak]]
```