Groff reader: got \f[] working properly.

This commit is contained in:
John MacFarlane 2018-10-25 00:16:35 -07:00
parent 718a947f7d
commit 02e515cada
2 changed files with 8 additions and 4 deletions

View file

@ -105,7 +105,8 @@ singleTok :: ManToken -> ManTokens
singleTok t = ManTokens (Seq.singleton t) singleTok t = ManTokens (Seq.singleton t)
data RoffState = RoffState { customMacros :: M.Map String ManTokens data RoffState = RoffState { customMacros :: M.Map String ManTokens
, lastFont :: FontSpec , prevFont :: FontSpec
, currentFont :: FontSpec
} deriving Show } deriving Show
instance Default RoffState where instance Default RoffState where
@ -117,7 +118,8 @@ instance Default RoffState where
, ("lq", "\x201C") , ("lq", "\x201C")
, ("rq", "\x201D") , ("rq", "\x201D")
, ("R", "\x00AE") ] , ("R", "\x00AE") ]
, lastFont = defaultFontSpec , prevFont = defaultFontSpec
, currentFont = defaultFontSpec
} }
type ManLexer m = ParserT [Char] RoffState m type ManLexer m = ParserT [Char] RoffState m
@ -261,7 +263,8 @@ escFont = do
, ($ defaultFontSpec) <$> letterFontKind , ($ defaultFontSpec) <$> letterFontKind
, lettersFont , lettersFont
] ]
modifyState $ \st -> st{ lastFont = font } modifyState $ \st -> st{ prevFont = currentFont st
, currentFont = font }
return [Font font] return [Font font]
lettersFont :: PandocMonad m => ManLexer m FontSpec lettersFont :: PandocMonad m => ManLexer m FontSpec
@ -271,7 +274,7 @@ lettersFont = try $ do
skipMany letter skipMany letter
char ']' char ']'
if null fs if null fs
then lastFont <$> getState then prevFont <$> getState
else return $ foldr ($) defaultFontSpec fs else return $ foldr ($) defaultFontSpec fs
letterFontKind :: PandocMonad m => ManLexer m (FontSpec -> FontSpec) letterFontKind :: PandocMonad m => ManLexer m (FontSpec -> FontSpec)

View file

@ -180,6 +180,7 @@ linePartsToInlines = go False
go :: Bool -> [LinePart] -> Inlines go :: Bool -> [LinePart] -> Inlines
go _ [] = mempty go _ [] = mempty
go mono (MacroArg _:xs) = go mono xs -- shouldn't happen go mono (MacroArg _:xs) = go mono xs -- shouldn't happen
go mono (RoffStr s : RoffStr t : xs) = go mono (RoffStr (s <> t):xs)
go mono (RoffStr s : xs) go mono (RoffStr s : xs)
| mono = code s <> go mono xs | mono = code s <> go mono xs
| otherwise = text s <> go mono xs | otherwise = text s <> go mono xs