Fix ghc 9.2.1 warnings.

This commit is contained in:
John MacFarlane 2021-12-30 18:23:15 -08:00
parent 2811468016
commit 4ff997bf68
5 changed files with 14 additions and 14 deletions

View file

@ -527,7 +527,7 @@ splitHeaderRows hasFirstRowFormatting rs = bimap reverse reverse $ fst
-- like trimInlines, but also take out linebreaks
trimSps :: Inlines -> Inlines
trimSps (Many ils) = Many $ Seq.dropWhileL isSp $Seq.dropWhileR isSp ils
trimSps (Many ils) = Many $ Seq.dropWhileL isSp $ Seq.dropWhileR isSp ils
where isSp Space = True
isSp SoftBreak = True
isSp LineBreak = True

View file

@ -153,7 +153,7 @@ singleItemHeaderToHeader blk = blk
blocksToBullets :: [Block] -> [Block]
blocksToBullets blks =
map singleItemHeaderToHeader $
bottomUp removeListDivs $flatToBullets (handleListParagraphs blks)
bottomUp removeListDivs $ flatToBullets (handleListParagraphs blks)
plainParaInlines :: Block -> [Inline]
plainParaInlines (Plain ils) = ils

View file

@ -125,7 +125,7 @@ header = tryMsg "header" $ do
skipSpaces
content <- B.trimInlines . mconcat <$> manyTill inline newline
attr <- registerHeader nullAttr content
return $B.headerWith attr level content
return $ B.headerWith attr level content
tableRow :: PandocMonad m => TikiWikiParser m [B.Blocks]
tableRow = try $ do
@ -163,11 +163,11 @@ table = try $ do
string "||"
newline
-- return $ B.simpleTable (headers rows) $ trace ("rows: " ++ (show rows)) rows
return $B.simpleTable (headers rows) rows
return $ B.simpleTable (headers rows) rows
where
-- The headers are as many empty strings as the number of columns
-- in the first row
headers rows = map (B.plain . B.str) $replicate (length $ head rows) ""
headers rows = replicate (length $ head rows) ((B.plain . B.str) "")
para :: PandocMonad m => TikiWikiParser m B.Blocks
para = fmap (result . mconcat) ( many1Till inline endOfParaElement)

View file

@ -216,7 +216,7 @@ definitionTerm1 = try $
definitionTerm2 :: PandocMonad m => VwParser m Inlines
definitionTerm2 = try $ trimInlines . mconcat <$> manyTill inline'
(try $lookAhead (defMarkerM >> notFollowedBy hasDefMarkerM))
(try $ lookAhead (defMarkerM >> notFollowedBy hasDefMarkerM))
defMarkerM :: PandocMonad m => VwParser m Char
defMarkerM = string "::" >> spaceChar
@ -382,7 +382,7 @@ bulletListMarkers = "ul" <$ (char '*' <|> char '-')
orderedListMarkers :: PandocMonad m => VwParser m Text
orderedListMarkers =
("ol" <$choice (orderedListMarker Decimal Period:(($OneParen) . orderedListMarker <$> [Decimal, LowerRoman, UpperRoman, LowerAlpha, UpperAlpha])))
("ol" <$ choice (orderedListMarker Decimal Period:(($ OneParen) . orderedListMarker <$> [Decimal, LowerRoman, UpperRoman, LowerAlpha, UpperAlpha])))
<|> ("ol" <$ char '#')
--many need trimInlines

View file

@ -105,13 +105,13 @@ writeRTF options doc = do
toc <- blocksToRTF 0 AlignDefault [toTableOfContents options blocks]
let context = defField "body" body
$ defField "spacer" spacer
$(if writerTableOfContents options
then defField "table-of-contents" toc
-- for backwards compatibility,
-- we populate toc with the contents
-- of the toc rather than a boolean:
. defField "toc" toc
else id) metadata
$ (if writerTableOfContents options
then defField "table-of-contents" toc
-- for backwards compatibility,
-- we populate toc with the contents
-- of the toc rather than a boolean:
. defField "toc" toc
else id) metadata
return $
case writerTemplate options of
Just tpl -> render Nothing $ renderTemplate tpl context