aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
diff options
context:
space:
mode:
authorChristian Despres <50160106+despresc@users.noreply.github.com>2020-09-13 10:48:14 -0400
committerGitHub <noreply@github.com>2020-09-13 07:48:14 -0700
commitcae155b095e5182cc1b342b21f7430e40afe7ba8 (patch)
tree82b6342b0a8dc6f98ce73188bb89ae5ad0267060 /src/Text/Pandoc/Readers/LaTeX/Parsing.hs
parent2109ded7101dba0ac48c9b60cdf454ad39a7e272 (diff)
downloadpandoc-cae155b095e5182cc1b342b21f7430e40afe7ba8.tar.gz
Fix hlint suggestions, update hlint.yaml (#6680)
* Fix hlint suggestions, update hlint.yaml Most suggestions were redundant brackets. Some required LambdaCase. The .hlint.yaml file had a small typo, and didn't ignore camelCase suggestions in certain modules.
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX/Parsing.hs')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs14
1 files changed, 6 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 10e48b45f..c349fe3b1 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -1,8 +1,8 @@
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Readers.LaTeX.Parsing
Copyright : Copyright (C) 2006-2020 John MacFarlane
@@ -736,14 +736,14 @@ keyval = try $ do
(mconcat <$> many1 (
(untokenize . snd <$> withRaw braced)
<|>
- (untokenize <$> (many1
+ (untokenize <$> many1
(satisfyTok
- (\t -> case t of
+ (\case
Tok _ Symbol "]" -> False
Tok _ Symbol "," -> False
Tok _ Symbol "{" -> False
Tok _ Symbol "}" -> False
- _ -> True))))))
+ _ -> True)))))
optional (symbol ',')
sp
return (key, T.strip val)
@@ -756,8 +756,7 @@ verbEnv name = withVerbatimMode $ do
optional blankline
res <- manyTill anyTok (end_ name)
return $ stripTrailingNewline
- $ untokenize
- $ res
+ $ untokenize res
-- Strip single final newline and any spaces following it.
-- Input is unchanged if it doesn't end with newline +
@@ -819,8 +818,7 @@ overlaySpecification = try $ do
overlayTok :: PandocMonad m => LP m Tok
overlayTok =
- satisfyTok (\t ->
- case t of
+ satisfyTok (\case
Tok _ Word _ -> True
Tok _ Spaces _ -> True
Tok _ Symbol c -> c `elem` ["-","+","@","|",":",","]