diff options
author | John MacFarlane <jgm@berkeley.edu> | 2018-03-17 22:00:55 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2018-03-17 22:00:55 -0700 |
commit | dfa1dc164a15389e00c86b8d97d71646827a74cf (patch) | |
tree | 882544c7e6e475d2e06988c3fedd54682a20764d /src/Text/Pandoc/Writers | |
parent | 73f9ba4a008b564ab901efb0bed325e4988df40d (diff) | |
download | pandoc-dfa1dc164a15389e00c86b8d97d71646827a74cf.tar.gz |
hlint fixes.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/DokuWiki.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Haddock.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Muse.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Shared.hs | 2 |
7 files changed, 22 insertions, 22 deletions
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 |