HLint: redundant parens
Remove parens enclosing a single element.
This commit is contained in:
parent
c35f5ba42d
commit
f6d151889c
8 changed files with 10 additions and 12 deletions
|
@ -1034,12 +1034,10 @@ main = do
|
|||
|
||||
variables' <- case mathMethod of
|
||||
LaTeXMathML Nothing -> do
|
||||
s <- readDataFileUTF8 datadir
|
||||
("LaTeXMathML.js")
|
||||
s <- readDataFileUTF8 datadir "LaTeXMathML.js"
|
||||
return $ ("mathml-script", s) : variables
|
||||
MathML Nothing -> do
|
||||
s <- readDataFileUTF8 datadir
|
||||
("MathMLinHTML.js")
|
||||
s <- readDataFileUTF8 datadir "MathMLinHTML.js"
|
||||
return $ ("mathml-script", s) : variables
|
||||
_ -> return variables
|
||||
|
||||
|
|
|
@ -730,7 +730,7 @@ listStart = bulletListStart <|> (anyOrderedListStart >> return ())
|
|||
listLine :: MarkdownParser String
|
||||
listLine = try $ do
|
||||
notFollowedBy' (do indentSpaces
|
||||
many (spaceChar)
|
||||
many spaceChar
|
||||
listStart)
|
||||
notFollowedBy' $ htmlTag (~== TagClose "div")
|
||||
chunks <- manyTill
|
||||
|
|
|
@ -594,7 +594,7 @@ surrounded border = enclosed (border *> notFollowedBy (oneOf " \t\n\r")) (try bo
|
|||
simpleInline :: Parser [Char] ParserState t -- ^ surrounding parser
|
||||
-> ([Inline] -> Inline) -- ^ Inline constructor
|
||||
-> Parser [Char] ParserState Inline -- ^ content parser (to be used repeatedly)
|
||||
simpleInline border construct = surrounded border (inlineWithAttribute) >>=
|
||||
simpleInline border construct = surrounded border inlineWithAttribute >>=
|
||||
return . construct . normalizeSpaces
|
||||
where inlineWithAttribute = (try $ optional attributes) >> inline
|
||||
|
||||
|
|
|
@ -524,7 +524,7 @@ blockToHtml opts (DefinitionList lst) = do
|
|||
contents <- mapM (\(term, defs) ->
|
||||
do term' <- if null term
|
||||
then return mempty
|
||||
else liftM (H.dt) $ inlineListToHtml opts term
|
||||
else liftM H.dt $ inlineListToHtml opts term
|
||||
defs' <- mapM ((liftM (\x -> H.dd $ (x >> nl opts))) .
|
||||
blockListToHtml opts) defs
|
||||
return $ mconcat $ nl opts : term' : nl opts :
|
||||
|
|
|
@ -51,7 +51,7 @@ data WriterState = WriterState {
|
|||
writeMediaWiki :: WriterOptions -> Pandoc -> String
|
||||
writeMediaWiki opts document =
|
||||
evalState (pandocToMediaWiki opts document)
|
||||
(WriterState { stNotes = False, stListLevel = [], stUseTags = False })
|
||||
WriterState { stNotes = False, stListLevel = [], stUseTags = False }
|
||||
|
||||
-- | Return MediaWiki representation of document.
|
||||
pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String
|
||||
|
|
|
@ -51,7 +51,7 @@ data WriterState = WriterState {
|
|||
writeTextile :: WriterOptions -> Pandoc -> String
|
||||
writeTextile opts document =
|
||||
evalState (pandocToTextile opts document)
|
||||
(WriterState { stNotes = [], stListLevel = [], stUseTags = False })
|
||||
WriterState { stNotes = [], stListLevel = [], stUseTags = False }
|
||||
|
||||
-- | Return Textile representation of document.
|
||||
pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
|
||||
|
|
|
@ -21,7 +21,7 @@ tests = [ testGroup "basic"
|
|||
[ "simple" =:
|
||||
"word" =?> para "word"
|
||||
, "space" =:
|
||||
"some text" =?> para ("some text")
|
||||
"some text" =?> para "some text"
|
||||
, "emphasized" =:
|
||||
"\\emph{emphasized}" =?> para (emph "emphasized")
|
||||
]
|
||||
|
|
|
@ -171,13 +171,13 @@ tests = [ testGroup "inline code"
|
|||
, testGroup "smart punctuation"
|
||||
[ test markdownSmart "quote before ellipses"
|
||||
("'...hi'"
|
||||
=?> para (singleQuoted ("…hi")))
|
||||
=?> para (singleQuoted "…hi"))
|
||||
, test markdownSmart "apostrophe before emph"
|
||||
("D'oh! A l'*aide*!"
|
||||
=?> para ("D’oh! A l’" <> emph "aide" <> "!"))
|
||||
, test markdownSmart "apostrophe in French"
|
||||
("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
|
||||
=?> para ("À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»"))
|
||||
=?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
|
||||
]
|
||||
, testGroup "mixed emphasis and strong"
|
||||
[ "emph and strong emph alternating" =:
|
||||
|
|
Loading…
Add table
Reference in a new issue