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/Powerpoint | |
parent | 73f9ba4a008b564ab901efb0bed325e4988df40d (diff) | |
download | pandoc-dfa1dc164a15389e00c86b8d97d71646827a74cf.tar.gz |
hlint fixes.
Diffstat (limited to 'src/Text/Pandoc/Writers/Powerpoint')
-rw-r--r-- | src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 20 |
1 files changed, 10 insertions, 10 deletions
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 |