aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-10-28 10:46:45 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-10-28 10:46:45 -0700
commitfdce771a4e56c5763c449cf41fbee33b69a11541 (patch)
treedec9b60ccea038653fd411a02d5c9cea3668a431
parentfe73707ab11a054aafad0ef6f1dc0ae54c4f67ad (diff)
downloadpandoc-fdce771a4e56c5763c449cf41fbee33b69a11541.tar.gz
Hlint changes.
-rw-r--r--src/Text/Pandoc/Readers/Man.hs11
-rw-r--r--src/Text/Pandoc/Readers/Roff.hs8
2 files changed, 9 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index f2fd4b0e1..89ac7ee51 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+
{-
Copyright (C) 2018 Yan Pashkovsky <yanp.bugz@gmail.com>
and John MacFarlane
@@ -224,7 +224,7 @@ mmacro mk = msatisfy isMMacro where
mmacroAny :: PandocMonad m => ManParser m RoffToken
mmacroAny = msatisfy isMMacro where
- isMMacro (MMacro{}) = True
+ isMMacro MMacro{} = True
isMMacro _ = False
--
@@ -387,8 +387,8 @@ parseCodeBlock = try $ do
| not (null ss)
, all isFontToken ss = Nothing
| otherwise = Just $ linePartsToString ss
- where isFontToken (FontSize{}) = True
- isFontToken (Font{}) = True
+ where isFontToken FontSize{} = True
+ isFontToken Font{} = True
isFontToken _ = False
extractText MEmptyLine = Just ""
-- string are intercalated with '\n', this prevents double '\n'
@@ -456,8 +456,7 @@ definitionListItem = try $ do
term <- parseInline
moreterms <- many $ try $ do
mmacro "TQ"
- newterm <- parseInline
- return newterm
+ parseInline
inls <- option mempty parseInlines
continuations <- mconcat <$> many continuation
return ( mconcat (intersperse B.linebreak (term:moreterms))
diff --git a/src/Text/Pandoc/Readers/Roff.hs b/src/Text/Pandoc/Readers/Roff.hs
index 085dfafd8..11da37953 100644
--- a/src/Text/Pandoc/Readers/Roff.hs
+++ b/src/Text/Pandoc/Readers/Roff.hs
@@ -247,7 +247,7 @@ escape = do
-- \s-1 \s0
escFontSize :: PandocMonad m => RoffLexer m [LinePart]
escFontSize = do
- let sign = option "" $ ("-" <$ char '-' <|> "" <$ char '+')
+ let sign = option "" ("-" <$ char '-' <|> "" <$ char '+')
let toFontSize xs =
case safeRead xs of
Nothing -> mzero
@@ -420,10 +420,10 @@ tableFormatSpecLine =
tableColFormat :: PandocMonad m => RoffLexer m CellFormat
tableColFormat = do
pipePrefix' <- option False
- $ True <$ (try $ string "|" <* notFollowedBy spacetab)
+ $ True <$ try (string "|" <* notFollowedBy spacetab)
c <- oneOf ['a','A','c','C','l','L','n','N','r','R','s','S','^','_','-',
'=','|']
- suffixes <- many $ (try $ skipMany spacetab *> count 1 digit) <|>
+ suffixes <- many $ try (skipMany spacetab *> count 1 digit) <|>
(do x <- oneOf ['b','B','d','D','e','E','f','F','i','I','m','M',
'p','P','t','T','u','U','v','V','w','W','x','X', 'z','Z']
num <- case toLower x of
@@ -441,7 +441,7 @@ tableColFormat = do
, pipePrefix = pipePrefix'
, pipeSuffix = pipeSuffix'
, columnSuffixes = suffixes }
-
+
-- We don't fully handle the conditional. But we do
-- include everything under '.ie n', which occurs commonly
-- in man pages. We always skip the '.el' part.