HLint: use elem
and notElem
Replaces long conditional chains with calls to `elem` and `notElem`.
This commit is contained in:
parent
1ed2c467c9
commit
0c5e7cf8cb
7 changed files with 20 additions and 24 deletions
|
@ -656,7 +656,7 @@ options =
|
|||
(ReqArg
|
||||
(\arg opt -> do
|
||||
let b = takeBaseName arg
|
||||
if (b == "pdflatex" || b == "lualatex" || b == "xelatex")
|
||||
if b `elem` ["pdflatex", "lualatex", "xelatex"]
|
||||
then return opt { optLaTeXEngine = arg }
|
||||
else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
|
||||
"PROGRAM")
|
||||
|
|
|
@ -271,7 +271,7 @@ spaceChar = satisfy $ \c -> c == ' ' || c == '\t'
|
|||
|
||||
-- | Parses a nonspace, nonnewline character.
|
||||
nonspaceChar :: Parser [Char] st Char
|
||||
nonspaceChar = satisfy $ \x -> x /= '\t' && x /= '\n' && x /= ' ' && x /= '\r'
|
||||
nonspaceChar = satisfy $ flip notElem ['\t', '\n', ' ', '\r']
|
||||
|
||||
-- | Skips zero or more spaces or tabs.
|
||||
skipSpaces :: Parser [Char] st ()
|
||||
|
@ -1062,7 +1062,7 @@ doubleQuoteStart :: Parser [Char] ParserState ()
|
|||
doubleQuoteStart = do
|
||||
failIfInQuoteContext InDoubleQuote
|
||||
try $ do charOrRef "\"\8220\147"
|
||||
notFollowedBy (satisfy (\c -> c == ' ' || c == '\t' || c == '\n'))
|
||||
notFollowedBy . satisfy $ flip elem [' ', '\t', '\n']
|
||||
|
||||
doubleQuoteEnd :: Parser [Char] st ()
|
||||
doubleQuoteEnd = do
|
||||
|
|
|
@ -874,9 +874,8 @@ verbatimEnv = do
|
|||
(_,r) <- withRaw $ do
|
||||
controlSeq "begin"
|
||||
name <- braced
|
||||
guard $ name == "verbatim" || name == "Verbatim" ||
|
||||
name == "lstlisting" || name == "minted" ||
|
||||
name == "alltt"
|
||||
guard $ name `elem` ["verbatim", "Verbatim", "lstlisting",
|
||||
"minted", "alltt"]
|
||||
verbEnv name
|
||||
rest <- getInput
|
||||
return (r,rest)
|
||||
|
|
|
@ -789,8 +789,8 @@ listItem start = try $ do
|
|||
orderedList :: MarkdownParser (F Blocks)
|
||||
orderedList = try $ do
|
||||
(start, style, delim) <- lookAhead anyOrderedListStart
|
||||
unless ((style == DefaultStyle || style == Decimal || style == Example) &&
|
||||
(delim == DefaultDelim || delim == Period)) $
|
||||
unless (style `elem` [DefaultStyle, Decimal, Example] &&
|
||||
delim `elem` [DefaultDelim, Period]) $
|
||||
guardEnabled Ext_fancy_lists
|
||||
when (style == Example) $ guardEnabled Ext_example_lists
|
||||
items <- fmap sequence $ many1 $ listItem
|
||||
|
@ -925,8 +925,8 @@ strictHtmlBlock = htmlInBalanced (not . isInlineTag)
|
|||
|
||||
rawVerbatimBlock :: MarkdownParser String
|
||||
rawVerbatimBlock = try $ do
|
||||
(TagOpen tag _, open) <- htmlTag (tagOpen (\t ->
|
||||
t == "pre" || t == "style" || t == "script")
|
||||
(TagOpen tag _, open) <- htmlTag (tagOpen (flip elem
|
||||
["pre", "style", "script"])
|
||||
(const True))
|
||||
contents <- manyTill anyChar (htmlTag (~== TagClose tag))
|
||||
return $ open ++ contents ++ renderTags [TagClose tag]
|
||||
|
|
|
@ -564,14 +564,10 @@ makeMeta title authors date =
|
|||
-- | Render HTML tags.
|
||||
renderTags' :: [Tag String] -> String
|
||||
renderTags' = renderTagsOptions
|
||||
renderOptions{ optMinimize = \x ->
|
||||
let y = map toLower x
|
||||
in y == "hr" || y == "br" ||
|
||||
y == "img" || y == "meta" ||
|
||||
y == "link"
|
||||
, optRawTag = \x ->
|
||||
let y = map toLower x
|
||||
in y == "script" || y == "style" }
|
||||
renderOptions{ optMinimize = matchTags ["hr", "br", "img",
|
||||
"meta", "link"]
|
||||
, optRawTag = matchTags ["script", "style"] }
|
||||
where matchTags = \tags -> flip elem tags . map toLower
|
||||
|
||||
--
|
||||
-- File handling
|
||||
|
|
|
@ -338,7 +338,7 @@ blockToMarkdown opts (RawBlock f str)
|
|||
else return $ if isEnabled Ext_markdown_attribute opts
|
||||
then text (addMarkdownAttribute str) <> text "\n"
|
||||
else text str <> text "\n"
|
||||
| f == "latex" || f == "tex" || f == "markdown" = do
|
||||
| f `elem` ["latex", "tex", "markdown"] = do
|
||||
st <- get
|
||||
if stPlain st
|
||||
then return empty
|
||||
|
@ -628,10 +628,11 @@ getReference label (src, tit) = do
|
|||
Nothing -> do
|
||||
let label' = case find ((== label) . fst) (stRefs st) of
|
||||
Just _ -> -- label is used; generate numerical label
|
||||
case find (\n -> not (any (== [Str (show n)])
|
||||
(map fst (stRefs st)))) [1..(10000 :: Integer)] of
|
||||
Just x -> [Str (show x)]
|
||||
Nothing -> error "no unique label"
|
||||
case find (\n -> notElem [Str (show n)]
|
||||
(map fst (stRefs st)))
|
||||
[1..(10000 :: Integer)] of
|
||||
Just x -> [Str (show x)]
|
||||
Nothing -> error "no unique label"
|
||||
Nothing -> label
|
||||
modify (\s -> s{ stRefs = (label', (src,tit)) : stRefs st })
|
||||
return label'
|
||||
|
|
|
@ -129,7 +129,7 @@ blockToOrg (Para inlines) = do
|
|||
blockToOrg (RawBlock "html" str) =
|
||||
return $ blankline $$ "#+BEGIN_HTML" $$
|
||||
nest 2 (text str) $$ "#+END_HTML" $$ blankline
|
||||
blockToOrg (RawBlock f str) | f == "org" || f == "latex" || f == "tex" =
|
||||
blockToOrg (RawBlock f str) | f `elem` ["org", "latex", "tex"] =
|
||||
return $ text str
|
||||
blockToOrg (RawBlock _ _) = return empty
|
||||
blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline
|
||||
|
|
Loading…
Reference in a new issue