aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Man.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Man.hs')
-rw-r--r--src/Text/Pandoc/Readers/Man.hs16
1 files changed, 9 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index 3644050c7..2c5d10b93 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -53,6 +53,7 @@ import Text.Pandoc.Readers.Roff -- TODO explicit imports
import Text.Parsec hiding (tokenPrim)
import qualified Text.Parsec as Parsec
import Text.Parsec.Pos (updatePosString, initialPos)
+import qualified Data.Sequence as Seq
import qualified Data.Foldable as Foldable
data ManState = ManState { readerOptions :: ReaderOptions
@@ -149,8 +150,9 @@ parseTable = do
isHrule ([cellfmt], _) = columnType cellfmt `elem` ['_','-','=']
isHrule (_, [RoffTokens ss]) =
case Foldable.toList ss of
- [MLine [RoffStr [c]]] -> c `elem` ['_','-','=']
- _ -> False
+ [MLine (LineParts (RoffStr [c] Seq.:<| Seq.Empty))]
+ -> c `elem` ['_','-','=']
+ _ -> False
isHrule _ = False
fallback pos = do
@@ -229,8 +231,8 @@ parseTitle = do
modifyState $ \st -> st{ metadata = adjustMeta $ metadata st }
return mempty
-linePartsToInlines :: [LinePart] -> Inlines
-linePartsToInlines = go False
+linePartsToInlines :: LineParts -> Inlines
+linePartsToInlines = go False . Foldable.toList . unLineParts
where
go :: Bool -> [LinePart] -> Inlines
@@ -366,10 +368,10 @@ parseCodeBlock = try $ do
where
extractText :: RoffToken -> Maybe String
- extractText (MLine ss)
- | not (null ss)
+ extractText (MLine (LineParts ss))
+ | not (Seq.null ss)
, all isFontToken ss = Nothing
- | otherwise = Just $ linePartsToString ss
+ | otherwise = Just $ linePartsToString (LineParts ss)
where isFontToken (FontSize{}) = True
isFontToken (Font{}) = True
isFontToken _ = False