From dfa1dc164a15389e00c86b8d97d71646827a74cf Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Sat, 17 Mar 2018 22:00:55 -0700
Subject: hlint fixes.

---
 src/Text/Pandoc/ImageSize.hs                       | 10 +++++-----
 src/Text/Pandoc/Lua/Util.hs                        |  2 +-
 src/Text/Pandoc/Readers/Docx.hs                    |  2 +-
 src/Text/Pandoc/Readers/Docx/Parse.hs              |  4 ++--
 src/Text/Pandoc/Readers/Markdown.hs                |  2 +-
 src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs        |  8 ++++----
 src/Text/Pandoc/Writers/Docx.hs                    |  6 +++---
 src/Text/Pandoc/Writers/DokuWiki.hs                |  4 ++--
 src/Text/Pandoc/Writers/EPUB.hs                    |  4 ++--
 src/Text/Pandoc/Writers/Haddock.hs                 |  4 ++--
 src/Text/Pandoc/Writers/Muse.hs                    |  4 ++--
 src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 20 ++++++++++----------
 src/Text/Pandoc/Writers/Shared.hs                  |  2 +-
 13 files changed, 36 insertions(+), 36 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 4c76aac13..e7698d148 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -126,7 +126,7 @@ imageType img = case B.take 4 img of
                        |  B.take 4 (B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
                                         -> return Eps
                      "\x01\x00\x00\x00"
-                       | B.take 4 (B.drop 40 img) == " EMF" 
+                       | B.take 4 (B.drop 40 img) == " EMF"
                                         -> return Emf
                      _                  -> mzero
 
@@ -361,9 +361,9 @@ svgSize opts img = do
   , dpiX = dpi
   , dpiY = dpi
   }
-  
+
 emfSize :: ByteString -> Maybe ImageSize
-emfSize img = 
+emfSize img =
   let
     parseheader = runGetOrFail $ do
       skip 0x18             -- 0x00
@@ -388,11 +388,11 @@ emfSize img =
         , dpiX = fromIntegral dpiW
         , dpiY = fromIntegral dpiH
         }
-  in 
+  in
     case parseheader . BL.fromStrict $ img of
       Left _ -> Nothing
       Right (_, _, size) -> Just size
-  
+
 
 jpegSize :: ByteString -> Either String ImageSize
 jpegSize img =
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index b7149af39..c1c40c299 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -132,7 +132,7 @@ class PushViaCall a where
 instance PushViaCall (Lua ()) where
   pushViaCall' fn pushArgs num = do
     Lua.push fn
-    Lua.rawget (Lua.registryindex)
+    Lua.rawget Lua.registryindex
     pushArgs
     call num 1
 
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 104e17c18..9b41e468a 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -367,7 +367,7 @@ blocksToInlinesWarn cmtId blks = do
 parPartToInlines :: PandocMonad m => ParPart -> DocxContext m Inlines
 parPartToInlines parPart =
   case parPart of
-    (BookMark _ anchor) | notElem anchor dummyAnchors -> do
+    (BookMark _ anchor) | anchor `notElem` dummyAnchors -> do
       inHdrBool <- asks docxInHeaderBlock
       ils <- parPartToInlines' parPart
       immedPrevAnchor <- gets docxImmedPrevAnchor
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index dcf2e0493..d6226dfab 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -136,9 +136,9 @@ unwrap :: NameSpaces -> Content -> [Content]
 unwrap ns (Elem element)
   | isElem ns "w" "sdt" element
   , Just sdtContent <- findChildByName ns "w" "sdtContent" element
-  = concatMap (unwrap ns) $ map Elem $ elChildren sdtContent
+  = concatMap ((unwrap ns) . Elem) (elChildren sdtContent)
   | isElem ns "w" "smartTag" element
-  = concatMap (unwrap ns) $ map Elem $ elChildren element
+  = concatMap ((unwrap ns) . Elem) (elChildren element)
 unwrap _ content = [content]
 
 unwrapChild :: NameSpaces -> Content -> Content
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 237f1aa0c..f6efef657 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -161,7 +161,7 @@ inlinesInBalancedBrackets =
         stripBracket xs = if last xs == ']' then init xs else xs
         go :: PandocMonad m => Int -> MarkdownParser m ()
         go 0 = return ()
-        go openBrackets = 
+        go openBrackets =
           (() <$ (escapedChar <|>
                 code <|>
                 rawHtmlInline <|>
diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
index ef8b2d18a..e9ce53704 100644
--- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
+++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs
@@ -61,13 +61,13 @@ and6 :: (Arrow a)
      => a b c0->a b c1->a b c2->a b c3->a b c4->a b c5
      -> a b (c0,c1,c2,c3,c4,c5      )
 
-and3 a b c           = (and2 a b          ) &&& c
+and3 a b c           = and2 a b &&& c
                        >>^ \((z,y          ) , x) -> (z,y,x          )
-and4 a b c d         = (and3 a b c        ) &&& d
+and4 a b c d         = and3 a b c &&& d
                        >>^ \((z,y,x        ) , w) -> (z,y,x,w        )
-and5 a b c d e       = (and4 a b c d      ) &&& e
+and5 a b c d e       = and4 a b c d &&& e
                        >>^ \((z,y,x,w      ) , v) -> (z,y,x,w,v      )
-and6 a b c d e f     = (and5 a b c d e    ) &&& f
+and6 a b c d e f     = and5 a b c d e &&& f
                        >>^ \((z,y,x,w,v    ) , u) -> (z,y,x,w,v,u    )
 
 liftA2 :: (Arrow a) => (x -> y -> z) -> a b x -> a b y -> a b z
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 2c03b3450..6422f61bf 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -1337,7 +1337,7 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do
         imgElt
 
   case stImage of
-    Just imgData -> return $ [generateImgElt imgData]
+    Just imgData -> return [generateImgElt imgData]
     Nothing -> ( do --try
       (img, mt) <- P.fetchItem src
       ident <- ("rId"++) `fmap` getUniqueId
@@ -1386,12 +1386,12 @@ breakElement kind = mknode "w:r" [] [mknode "w:br" [("w:type",kind)] () ]
 defaultFootnotes :: [Element]
 defaultFootnotes = [ mknode "w:footnote"
                      [("w:type", "separator"), ("w:id", "-1")]
-                     [ mknode "w:p" [] $
+                     [ mknode "w:p" []
                        [mknode "w:r" [] $
                         [ mknode "w:separator" [] ()]]]
                    , mknode "w:footnote"
                      [("w:type", "continuationSeparator"), ("w:id", "0")]
-                     [ mknode "w:p" [] $
+                     [ mknode "w:p" []
                        [ mknode "w:r" [] $
                          [ mknode "w:continuationSeparator" [] ()]]]]
 
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 523830e28..a74c23764 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -372,9 +372,9 @@ backSlashLineBreaks :: [String] -> String
 backSlashLineBreaks ls = vcatBackSlash $ map escape ls
   where
     vcatBackSlash = intercalate "\\\\ \\\\ " -- simulate paragraphs.
-    escape ('\n':[]) = "" -- remove trailing newlines
+    escape ['\n'] = "" -- remove trailing newlines
     escape ('\n':cs) = "\\\\ " ++ escape cs
-    escape (c:cs)    = c : (escape cs)
+    escape (c:cs)    = c : escape cs
     escape []        = []
 
 -- Auxiliary functions for tables:
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 7b4853a24..cf50e9bb9 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -458,7 +458,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
   -- mediaRef <- P.newIORef []
   Pandoc _ blocks <- walkM (transformInline opts') doc >>=
                      walkM transformBlock
-  picEntries <- (mapMaybe (snd . snd)) <$> gets stMediaPaths
+  picEntries <- mapMaybe (snd . snd) <$> gets stMediaPaths
   -- handle fonts
   let matchingGlob f = do
         xs <- lift $ P.glob f
@@ -872,7 +872,7 @@ metadataElement version md currentTime =
         dcTag' n s = [dcTag n s]
         toIdentifierNode id' (Identifier txt scheme)
           | version == EPUB2 = [dcNode "identifier" !
-              ([("id",id')] ++ maybe [] (\x -> [("opf:scheme", x)]) scheme) $
+              (("id",id') : maybe [] (\x -> [("opf:scheme", x)]) scheme) $
               txt]
           | otherwise = [dcNode "identifier" ! [("id",id')] $ txt] ++
               maybe [] (\x -> [unode "meta" !
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 3f96f5802..dfa1d8b57 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE OverloadedStrings   #-}
 {-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TupleSections       #-}
+
 {-
 Copyright (C) 2014-2015, 2017-2018 John MacFarlane <jgm@berkeley.edu>
 
@@ -141,7 +141,7 @@ blockToHaddock opts (Table caption aligns widths headers rows) = do
                      then empty
                      else blankline <> caption' <> blankline
   tbl <- gridTable opts blockListToHaddock
-              (all null headers) (map (\_ -> AlignDefault) aligns)
+              (all null headers) (map (const AlignDefault) aligns)
                 widths headers rows
   return $ prefixed "> " (tbl $$ blankline $$ caption'') $$ blankline
 blockToHaddock opts (BulletList items) = do
diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index 8a8217d94..5dda951c5 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -373,7 +373,7 @@ inlineToMuse (Superscript lst) = do
 inlineToMuse (Subscript lst) = do
   contents <- inlineListToMuse lst
   return $ "<sub>" <> contents <> "</sub>"
-inlineToMuse (SmallCaps {}) =
+inlineToMuse SmallCaps {} =
   fail "SmallCaps should be expanded before normalization"
 inlineToMuse (Quoted SingleQuote lst) = do
   contents <- inlineListToMuse lst
@@ -381,7 +381,7 @@ inlineToMuse (Quoted SingleQuote lst) = do
 inlineToMuse (Quoted DoubleQuote lst) = do
   contents <- inlineListToMuse lst
   return $ "“" <> contents <> "”"
-inlineToMuse (Cite {}) =
+inlineToMuse Cite {} =
   fail "Citations should be expanded before normalization"
 inlineToMuse (Code _ str) = return $
   "<code>" <> text (substitute "</code>" "<</code><code>/code>" str) <> "</code>"
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 396469edd..fcd124e76 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -474,7 +474,7 @@ blockToParagraphs (DefinitionList entries) = do
         definition <- concatMapM (blockToParagraphs . BlockQuote) blksLst
         return $ term ++ definition
   concatMapM go entries
-blockToParagraphs (Div (_, "notes" : [], _) blks) =
+blockToParagraphs (Div (_, ["notes"], _) blks) =
   local (\env -> env{envInSpeakerNotes=True}) $ do
   sldId <- asks envCurSlideId
   spkNotesMap <- gets stSpeakerNotesMap
@@ -558,7 +558,7 @@ blockToShape blk = do paras <- blockToParagraphs blk
 combineShapes :: [Shape] -> [Shape]
 combineShapes [] = []
 combineShapes[s] = [s]
-combineShapes (pic@(Pic{}) : ss) = pic : combineShapes ss
+combineShapes (pic@Pic{} : ss) = pic : combineShapes ss
 combineShapes (TextBox [] : ss) = combineShapes ss
 combineShapes (s : TextBox [] : ss) = combineShapes (s : ss)
 combineShapes (TextBox (p:ps) : TextBox (p':ps') : ss) =
@@ -569,8 +569,8 @@ blocksToShapes :: [Block] -> Pres [Shape]
 blocksToShapes blks = combineShapes <$> mapM blockToShape blks
 
 isImage :: Inline -> Bool
-isImage (Image{}) = True
-isImage (Link _ (Image _ _ _ : _) _) = True
+isImage Image{} = True
+isImage (Link _ (Image{} : _) _) = True
 isImage _ = False
 
 splitBlocks' :: [Block] -> [[Block]] -> [Block] -> Pres [[Block]]
@@ -589,23 +589,23 @@ splitBlocks' cur acc (Plain ils : blks) = splitBlocks' cur acc (Para ils : blks)
 splitBlocks' cur acc (Para (il:ils) : blks) | isImage il = do
   slideLevel <- asks envSlideLevel
   case cur of
-    [(Header n _ _)] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel ->
                             splitBlocks' []
                             (acc ++ [cur ++ [Para [il]]])
                             (if null ils then blks else Para ils : blks)
     _ -> splitBlocks' []
          (acc ++ (if null cur then [] else [cur]) ++ [[Para [il]]])
          (if null ils then blks else Para ils : blks)
-splitBlocks' cur acc (tbl@(Table{}) : blks) = do
+splitBlocks' cur acc (tbl@Table{} : blks) = do
   slideLevel <- asks envSlideLevel
   case cur of
-    [(Header n _ _)] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel ->
                             splitBlocks' [] (acc ++ [cur ++ [tbl]]) blks
     _ ->  splitBlocks' [] (acc ++ (if null cur then [] else [cur]) ++ [[tbl]]) blks
 splitBlocks' cur acc (d@(Div (_, classes, _) _): blks) | "columns" `elem` classes =  do
   slideLevel <- asks envSlideLevel
   case cur of
-    [(Header n _ _)] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel ->
                             splitBlocks' [] (acc ++ [cur ++ [d]]) blks
     _ ->  splitBlocks' [] (acc ++ (if null cur then [] else [cur]) ++ [[d]]) blks
 splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks
@@ -617,7 +617,7 @@ getSpeakerNotes :: Pres (Maybe SpeakerNotes)
 getSpeakerNotes = do
   sldId <- asks envCurSlideId
   spkNtsMap <- gets stSpeakerNotesMap
-  return $ (SpeakerNotes . concat . reverse) <$> (M.lookup sldId spkNtsMap)
+  return $ (SpeakerNotes . concat . reverse) <$> M.lookup sldId spkNtsMap
 
 blocksToSlide' :: Int -> [Block] -> Pres Slide
 blocksToSlide' lvl (Header n (ident, _, _) ils : blks)
@@ -864,7 +864,7 @@ emptyParagraph para = all emptyParaElem $ paraElems para
 
 
 emptyShape :: Shape -> Bool
-emptyShape (TextBox paras) = all emptyParagraph $ paras
+emptyShape (TextBox paras) = all emptyParagraph paras
 emptyShape _ = False
 
 emptyLayout :: Layout -> Bool
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index a0482fdbf..964db5ecc 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -289,7 +289,7 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do
   -- on command line options, widths given in this specific table, and
   -- cells' contents
   let handleWidths
-        | (writerWrapText opts) == WrapNone  = handleFullWidths
+        | writerWrapText opts == WrapNone  = handleFullWidths
         | all (== 0) widths                  = handleZeroWidths
         | otherwise                          = handleGivenWidths widths
   (widthsInChars, rawHeaders, rawRows) <- handleWidths
-- 
cgit v1.2.3