diff options
Diffstat (limited to 'src/Text')
57 files changed, 260 insertions, 290 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index dec7ae41e..4b9e691ed 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE OverloadedStrings #-} @@ -868,9 +869,7 @@ options = , Option "" ["print-highlight-style"] (ReqArg (\arg opt -> do - let write = case optOutputFile opt of - Just f -> B.writeFile f - Nothing -> B.putStr + let write = maybe B.putStr B.writeFile $ optOutputFile opt sty <- runIOorExplode $ lookupHighlightStyle arg write $ encodePretty' defConfig{confIndent = Spaces 4 @@ -1017,7 +1016,7 @@ lookupHighlightStyle s deprecatedOption :: String -> String -> IO () deprecatedOption o msg = runIO (report $ Deprecated (T.pack o) (T.pack msg)) >>= - \r -> case r of + \case Right () -> return () Left e -> E.throwIO e diff --git a/src/Text/Pandoc/Class/PandocMonad.hs b/src/Text/Pandoc/Class/PandocMonad.hs index 991aeed41..a454de1d0 100644 --- a/src/Text/Pandoc/Class/PandocMonad.hs +++ b/src/Text/Pandoc/Class/PandocMonad.hs @@ -433,7 +433,7 @@ getDefaultReferenceDocx = do "word/theme/theme1.xml"] let toLazy = BL.fromChunks . (:[]) let pathToEntry path = do - epochtime <- (floor . utcTimeToPOSIXSeconds) <$> getCurrentTime + epochtime <- floor . utcTimeToPOSIXSeconds <$> getCurrentTime contents <- toLazy <$> readDataFile ("docx/" ++ path) return $ toEntry path epochtime contents datadir <- getUserDataDir @@ -536,7 +536,7 @@ getDefaultReferencePptx = do ] let toLazy = BL.fromChunks . (:[]) let pathToEntry path = do - epochtime <- (floor . utcTimeToPOSIXSeconds) <$> getCurrentTime + epochtime <- floor . utcTimeToPOSIXSeconds <$> getCurrentTime contents <- toLazy <$> readDataFile ("pptx/" ++ path) return $ toEntry path epochtime contents datadir <- getUserDataDir @@ -568,11 +568,11 @@ readDataFile fname = do -- | Read file from from Cabal data directory. readDefaultDataFile :: PandocMonad m => FilePath -> m B.ByteString readDefaultDataFile "reference.docx" = - (B.concat . BL.toChunks . fromArchive) <$> getDefaultReferenceDocx + B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceDocx readDefaultDataFile "reference.pptx" = - (B.concat . BL.toChunks . fromArchive) <$> getDefaultReferencePptx + B.concat . BL.toChunks . fromArchive <$> getDefaultReferencePptx readDefaultDataFile "reference.odt" = - (B.concat . BL.toChunks . fromArchive) <$> getDefaultReferenceODT + B.concat . BL.toChunks . fromArchive <$> getDefaultReferenceODT readDefaultDataFile fname = #ifdef EMBED_DATA_FILES case lookup (makeCanonical fname) dataFiles of diff --git a/src/Text/Pandoc/Image.hs b/src/Text/Pandoc/Image.hs index 58339f6b2..e37de4e00 100644 --- a/src/Text/Pandoc/Image.hs +++ b/src/Text/Pandoc/Image.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Image Copyright : Copyright (C) 2020 John MacFarlane diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs index 4ac9551f5..af59316b5 100644 --- a/src/Text/Pandoc/Logging.hs +++ b/src/Text/Pandoc/Logging.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Logging @@ -51,8 +52,7 @@ instance FromJSON Verbosity where parseJSON _ = mzero instance FromYAML Verbosity where - parseYAML = withStr "Verbosity" $ \t -> - case t of + parseYAML = withStr "Verbosity" $ \case "ERROR" -> return ERROR "WARNING" -> return WARNING "INFO" -> return INFO diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index 7a75047ae..679dd1f46 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -230,9 +230,7 @@ peekCaption idx = do instance Peekable ColWidth where peek idx = do width <- Lua.fromOptional <$> Lua.peek idx - return $ case width of - Nothing -> ColWidthDefault - Just w -> ColWidth w + return $ maybe ColWidthDefault ColWidth width instance Pushable ColWidth where push = \case diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index 4fe5e255d..988489a2a 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -50,9 +50,8 @@ pushModule = do -- | Squashes a list of blocks into inlines. blocksToInlines :: [Block] -> Lua.Optional [Inline] -> PandocLua [Inline] blocksToInlines blks optSep = liftPandocLua $ do - let sep = case Lua.fromOptional optSep of - Just x -> B.fromList x - Nothing -> Shared.defaultBlocksSeparator + let sep = maybe Shared.defaultBlocksSeparator B.fromList + $ Lua.fromOptional optSep return $ B.toList (Shared.blocksToInlinesWithSep sep blks) -- | Convert list of Pandoc blocks into sections using Divs. diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 664b84123..a5d79d319 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,8 +1,9 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TemplateHaskell #-} {- | Module : Text.Pandoc.Options Copyright : Copyright (C) 2012-2020 John MacFarlane @@ -327,7 +328,7 @@ $(deriveJSON defaultOptions{ constructorTagModifier = } ''CiteMethod) $(deriveJSON defaultOptions{ constructorTagModifier = - \t -> case t of + \case "NoObfuscation" -> "none" "ReferenceObfuscation" -> "references" "JavascriptObfuscation" -> "javascript" diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 4c69efd96..01dc45d24 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {- | @@ -201,8 +202,7 @@ convertImage opts tmpdir fname = do (\(e :: E.SomeException) -> return $ Left $ "check that rsvg-convert is in path.\n" <> tshow e) - _ -> JP.readImage fname >>= \res -> - case res of + _ -> JP.readImage fname >>= \case Left e -> return $ Left $ T.pack e Right img -> E.catch (Right pngOut <$ JP.savePngImage pngOut img) $ diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index c6c80eee4..953851966 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -574,15 +574,15 @@ romanNumeral upperCase = do let fivehundred = rchar 'D' let thousand = rchar 'M' lookAhead $ choice [one, five, ten, fifty, hundred, fivehundred, thousand] - thousands <- ((1000 *) . length) <$> many thousand + thousands <- (1000 *) . length <$> many thousand ninehundreds <- option 0 $ try $ hundred >> thousand >> return 900 fivehundreds <- option 0 $ 500 <$ fivehundred fourhundreds <- option 0 $ try $ hundred >> fivehundred >> return 400 - hundreds <- ((100 *) . length) <$> many hundred + hundreds <- (100 *) . length <$> many hundred nineties <- option 0 $ try $ ten >> hundred >> return 90 fifties <- option 0 (50 <$ fifty) forties <- option 0 $ try $ ten >> fifty >> return 40 - tens <- ((10 *) . length) <$> many ten + tens <- (10 *) . length <$> many ten nines <- option 0 $ try $ one >> ten >> return 9 fives <- option 0 (5 <$ five) fours <- option 0 $ try $ one >> five >> return 4 @@ -951,7 +951,7 @@ tableWith' headerParser rowParser lineParser footerParser = try $ do then replicate (length aligns) 0.0 else widthsFromIndices numColumns indices let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return (aligns, widths, toHeaderRow <$> heads, map toRow <$> lines') -- Calculate relative widths of table columns, based on indices @@ -1170,7 +1170,7 @@ class HasReaderOptions st where extractReaderOptions :: st -> ReaderOptions getOption :: (Stream s m t) => (ReaderOptions -> b) -> ParserT s st m b -- default - getOption f = (f . extractReaderOptions) <$> getState + getOption f = f . extractReaderOptions <$> getState instance HasReaderOptions ParserState where extractReaderOptions = stateOptions @@ -1492,10 +1492,8 @@ extractIdClass :: Attr -> Attr extractIdClass (ident, cls, kvs) = (ident', cls', kvs') where ident' = fromMaybe ident (lookup "id" kvs) - cls' = case lookup "class" kvs of - Just cl -> T.words cl - Nothing -> cls - kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs + cls' = maybe cls T.words $ lookup "class" kvs + kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs insertIncludedFile' :: (PandocMonad m, HasIncludeFiles st) => ParserT a st m (mf Blocks) diff --git a/src/Text/Pandoc/Readers/CSV.hs b/src/Text/Pandoc/Readers/CSV.hs index 384687a6a..f0edcaa16 100644 --- a/src/Text/Pandoc/Readers/CSV.hs +++ b/src/Text/Pandoc/Readers/CSV.hs @@ -39,7 +39,7 @@ readCSV _opts s = numcols = length r toplain = B.simpleCell . B.plain . B.text . T.strip toRow = Row nullAttr . map toplain - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] hdrs = toHeaderRow r rows = map toRow rs aligns = replicate numcols AlignDefault diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index a85d9aa37..43db6d59a 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -1,6 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Readers.CommonMark Copyright : Copyright (C) 2015-2020 John MacFarlane diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index b91e29fa7..084c2788f 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -18,7 +18,7 @@ import Data.Either (rights) import Data.Foldable (asum) import Data.Generics import Data.List (intersperse,elemIndex) -import Data.Maybe (fromMaybe,catMaybes) +import Data.Maybe (fromMaybe,mapMaybe) import Data.Text (Text) import qualified Data.Text as T import Text.HTML.TagSoup.Entity (lookupEntity) @@ -781,7 +781,7 @@ parseBlock (Elem e) = "para" -> parseMixed para (elContent e) "formalpara" -> do tit <- case filterChild (named "title") e of - Just t -> (para . strong . (<> str ".")) <$> + Just t -> para . strong . (<> str ".") <$> getInlines t Nothing -> return mempty (tit <>) <$> parseMixed para (elContent e) @@ -897,7 +897,7 @@ parseBlock (Elem e) = parseBlockquote = do attrib <- case filterChild (named "attribution") e of Nothing -> return mempty - Just z -> (para . (str "— " <>) . mconcat) + Just z -> para . (str "— " <>) . mconcat <$> mapM parseInline (elContent z) contents <- getBlocks e @@ -931,7 +931,7 @@ parseBlock (Elem e) = _ -> filterChildren isColspec e' let colnames = case colspecs of [] -> [] - cs -> catMaybes $ map (findAttr (unqual "colname" )) cs + cs -> mapMaybe (findAttr (unqual "colname" )) cs let isRow x = named "row" x || named "tr" x headrows <- case filterChild (named "thead") e' of Just h -> case filterChild isRow h of @@ -968,7 +968,7 @@ parseBlock (Elem e) = in ColWidth . (/ tot) <$> ws' Nothing -> replicate numrows ColWidthDefault let toRow = Row nullAttr - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ table (simpleCaption $ plain capt) (zip aligns widths) (TableHead nullAttr $ toHeaderRow headrows) @@ -1008,7 +1008,7 @@ parseBlock (Elem e) = parseMixed :: PandocMonad m => (Inlines -> Blocks) -> [Content] -> DB m Blocks parseMixed container conts = do let (ils,rest) = break isBlockElement conts - ils' <- (trimInlines . mconcat) <$> mapM parseInline ils + ils' <- trimInlines . mconcat <$> mapM parseInline ils let p = if ils' == mempty then mempty else container ils' case rest of [] -> return p @@ -1036,10 +1036,10 @@ parseEntry cn el = do case (mStrt, mEnd) of (Just start, Just end) -> colDistance start end _ -> 1 - (fmap (cell AlignDefault 1 (toColSpan el)) . (parseMixed plain) . elContent) el + (fmap (cell AlignDefault 1 (toColSpan el)) . parseMixed plain . elContent) el getInlines :: PandocMonad m => Element -> DB m Inlines -getInlines e' = (trimInlines . mconcat) <$> +getInlines e' = trimInlines . mconcat <$> mapM parseInline (elContent e') strContentRecursive :: Element -> String @@ -1136,7 +1136,7 @@ parseInline (Elem e) = "strong" -> strong <$> innerInlines "strikethrough" -> strikeout <$> innerInlines _ -> emph <$> innerInlines - "footnote" -> (note . mconcat) <$> + "footnote" -> note . mconcat <$> mapM parseBlock (elContent e) "title" -> return mempty "affiliation" -> skip @@ -1149,14 +1149,14 @@ parseInline (Elem e) = lift $ report $ IgnoredElement $ T.pack $ qName (elName e) return mempty - innerInlines = (trimInlines . mconcat) <$> + innerInlines = trimInlines . mconcat <$> mapM parseInline (elContent e) codeWithLang = do let classes' = case attrValue "language" e of "" -> [] l -> [l] return $ codeWith (attrValue "id" e,classes',[]) $ T.pack $ strContentRecursive e - simpleList = (mconcat . intersperse (str "," <> space)) <$> mapM getInlines + simpleList = mconcat . intersperse (str "," <> space) <$> mapM getInlines (filterChildren (named "member") e) segmentedList = do tit <- maybe (return mempty) getInlines $ filterChild (named "title") e diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index c9aa2f7c5..9c2f58342 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -91,9 +91,9 @@ readDocx :: PandocMonad m => ReaderOptions -> B.ByteString -> m Pandoc -readDocx opts bytes = do +readDocx opts bytes = case toArchiveOrFail bytes of - Right archive -> do + Right archive -> case archiveToDocxWithWarnings archive of Right (docx, parserWarnings) -> do mapM_ (P.report . DocxParserWarning) parserWarnings @@ -291,9 +291,9 @@ runStyleToTransform rPr' = do spanWith ("",[],[("dir","ltr")]) . go rPr{isRTL = Nothing} | Just SupScrpt <- rVertAlign rPr = superscript . go rPr{rVertAlign = Nothing} - | Just SubScrpt <- rVertAlign rPr = do + | Just SubScrpt <- rVertAlign rPr = subscript . go rPr{rVertAlign = Nothing} - | Just "single" <- rUnderline rPr = do + | Just "single" <- rUnderline rPr = Pandoc.underline . go rPr{rUnderline = Nothing} | otherwise = id return $ go rPr' @@ -658,7 +658,7 @@ bodyPartToBlocks (Tbl cap _ look parts@(r:rs)) = do rowLength (Docx.Row c) = length c let toRow = Pandoc.Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] -- pad cells. New Text.Pandoc.Builder will do that for us, -- so this is for compatibility while we switch over. diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index eab4f4e0d..698d7a88a 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -404,12 +404,8 @@ archiveToNotes zf = >>= (parseXMLDoc . UTF8.toStringLazy . fromEntry) enElem = findEntryByPath "word/endnotes.xml" zf >>= (parseXMLDoc . UTF8.toStringLazy . fromEntry) - fn_namespaces = case fnElem of - Just e -> elemToNameSpaces e - Nothing -> [] - en_namespaces = case enElem of - Just e -> elemToNameSpaces e - Nothing -> [] + fn_namespaces = maybe [] elemToNameSpaces fnElem + en_namespaces = maybe [] elemToNameSpaces enElem ns = unionBy (\x y -> fst x == fst y) fn_namespaces en_namespaces fn = fnElem >>= walkDocument ns >>= elemToNotes ns "footnote" en = enElem >>= walkDocument ns >>= elemToNotes ns "endnote" @@ -420,9 +416,7 @@ archiveToComments :: Archive -> Comments archiveToComments zf = let cmtsElem = findEntryByPath "word/comments.xml" zf >>= (parseXMLDoc . UTF8.toStringLazy . fromEntry) - cmts_namespaces = case cmtsElem of - Just e -> elemToNameSpaces e - Nothing -> [] + cmts_namespaces = maybe [] elemToNameSpaces cmtsElem cmts = elemToComments cmts_namespaces <$> (cmtsElem >>= walkDocument cmts_namespaces) in case cmts of diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs index 722701ee2..336be09e5 100644 --- a/src/Text/Pandoc/Readers/DokuWiki.hs +++ b/src/Text/Pandoc/Readers/DokuWiki.hs @@ -472,7 +472,7 @@ table = do else ([], rows) let attrs = (AlignDefault, ColWidthDefault) <$ transpose rows let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] pure $ B.table B.emptyCaption attrs (TableHead nullAttr $ toHeaderRow headerRow) diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 3f6e0a1af..761c4cabe 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -517,7 +517,7 @@ pTable = try $ do else replicate cols (ColWidth (1.0 / fromIntegral cols)) else widths' let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.tableWith attribs (B.simpleCaption $ B.plain caption) (zip aligns widths) diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 8fe5e062c..25d69f040 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -86,7 +86,7 @@ docHToBlocks d' = } -> let toCells = map (docHToBlocks . tableCellContents) . tableRowCells toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] (header, body) = if null headerRows then ([], map toCells bodyRows) diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs index d3d742de3..69d597212 100644 --- a/src/Text/Pandoc/Readers/JATS.hs +++ b/src/Text/Pandoc/Readers/JATS.hs @@ -189,7 +189,7 @@ parseBlock (Elem e) = _ -> getBlocks e where parseMixed container conts = do let (ils,rest) = break isBlockElement conts - ils' <- (trimInlines . mconcat) <$> mapM parseInline ils + ils' <- trimInlines . mconcat <$> mapM parseInline ils let p = if ils' == mempty then mempty else container ils' case rest of [] -> return p @@ -206,7 +206,7 @@ parseBlock (Elem e) = parseBlockquote = do attrib <- case filterChild (named "attribution") e of Nothing -> return mempty - Just z -> (para . (str "— " <>) . mconcat) + Just z -> para . (str "— " <>) . mconcat <$> mapM parseInline (elContent z) contents <- getBlocks e @@ -281,7 +281,7 @@ parseBlock (Elem e) = in ColWidth . (/ tot) <$> ws' Nothing -> replicate numrows ColWidthDefault let toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ table (simpleCaption $ plain capt) (zip aligns widths) (TableHead nullAttr $ toHeaderRow headrows) @@ -309,7 +309,7 @@ parseBlock (Elem e) = return $ headerWith (ident,[],[]) n' headerText <> b getInlines :: PandocMonad m => Element -> JATS m Inlines -getInlines e' = (trimInlines . mconcat) <$> +getInlines e' = trimInlines . mconcat <$> mapM parseInline (elContent e') parseMetadata :: PandocMonad m => Element -> JATS m Blocks @@ -518,10 +518,10 @@ parseInline (Elem e) = "email" -> return $ link ("mailto:" <> textContent e) "" $ str $ textContent e "uri" -> return $ link (textContent e) "" $ str $ textContent e - "fn" -> (note . mconcat) <$> + "fn" -> note . mconcat <$> mapM parseBlock (elContent e) _ -> innerInlines - where innerInlines = (trimInlines . mconcat) <$> + where innerInlines = trimInlines . mconcat <$> mapM parseInline (elContent e) mathML x = case readMathML . T.pack . showElement $ everywhere (mkT removePrefix) x of diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index de391e54a..5ceb6e22a 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -31,6 +31,7 @@ import Control.Monad import Control.Monad.Except (throwError) import Data.Char (isDigit, isLetter, toUpper, chr) import Data.Default +import Data.Functor (($>)) import Data.List (intercalate) import qualified Data.Map as M import Data.Maybe (fromMaybe, maybeToList) @@ -136,15 +137,15 @@ rawLaTeXBlock = do inp <- getInput let toks = tokenize "source" inp snd <$> (rawLaTeXParser toks False (macroDef (const mempty)) blocks - <|> (rawLaTeXParser toks True + <|> rawLaTeXParser toks True (do choice (map controlSeq ["include", "input", "subfile", "usepackage"]) skipMany opt braced - return mempty) blocks) + return mempty) blocks <|> rawLaTeXParser toks True (environment <|> blockCommand) - (mconcat <$> (many (block <|> beginOrEndCommand)))) + (mconcat <$> many (block <|> beginOrEndCommand))) -- See #4667 for motivation; sometimes people write macros -- that just evaluate to a begin or end command, which blockCommand @@ -187,10 +188,10 @@ inlineCommand = do -- inline elements: word :: PandocMonad m => LP m Inlines -word = (str . untoken) <$> satisfyTok isWordTok +word = str . untoken <$> satisfyTok isWordTok regularSymbol :: PandocMonad m => LP m Inlines -regularSymbol = (str . untoken) <$> satisfyTok isRegularSymbol +regularSymbol = str . untoken <$> satisfyTok isRegularSymbol where isRegularSymbol (Tok _ Symbol t) = not $ T.any isSpecial t isRegularSymbol _ = False isSpecial c = c `Set.member` specialChars @@ -206,7 +207,7 @@ inlineGroup = do doLHSverb :: PandocMonad m => LP m Inlines doLHSverb = - (codeWith ("",["haskell"],[]) . untokenize) + codeWith ("",["haskell"],[]) . untokenize <$> manyTill (satisfyTok (not . isNewlineTok)) (symbol '|') mkImage :: PandocMonad m => [(Text, Text)] -> Text -> LP m Inlines @@ -342,7 +343,7 @@ doverb = do Just (c, ts) | T.null ts -> return c _ -> mzero withVerbatimMode $ - (code . untokenize) <$> + code . untokenize <$> manyTill (notFollowedBy newlineTok >> verbTok marker) (symbol marker) verbTok :: PandocMonad m => Char -> LP m Tok @@ -383,7 +384,7 @@ doinlinecode classes = do _ -> mzero let stopchar = if marker == '{' then '}' else marker withVerbatimMode $ - (codeWith ("",classes,[]) . T.map nlToSpace . untokenize) <$> + codeWith ("",classes,[]) . T.map nlToSpace . untokenize <$> manyTill (verbTok stopchar) (symbol stopchar) nlToSpace :: Char -> Char @@ -402,7 +403,7 @@ dollarsMath = do display <- option False (True <$ symbol '$') (do contents <- try $ untokenize <$> pDollarsMath 0 if display - then (mathDisplay contents <$ symbol '$') + then mathDisplay contents <$ symbol '$' else return $ mathInline contents) <|> (guard display >> return (mathInline "")) @@ -415,7 +416,7 @@ pDollarsMath n = do , n == 0 -> return [] | t == "\\" -> do tk' <- anyTok - ((tk :) . (tk' :)) <$> pDollarsMath n + (tk :) . (tk' :) <$> pDollarsMath n | t == "{" -> (tk :) <$> pDollarsMath (n+1) | t == "}" -> if n > 0 @@ -477,7 +478,7 @@ cites mode multi = try $ do tempCits <- many1 simpleCiteArgs case tempCits of (k:ks) -> case ks of - (_:_) -> return $ ((addMprenote pre k):init ks) ++ + (_:_) -> return $ (addMprenote pre k : init ks) ++ [addMpostnote suf (last ks)] _ -> return [addMprenote pre (addMpostnote suf k)] _ -> return [[]] @@ -521,7 +522,7 @@ complexNatbibCitation mode = try $ do bgroup items <- mconcat <$> many1 (notFollowedBy (symbol ';') >> inline) - `sepBy1` (symbol ';') + `sepBy1` symbol ';' egroup return $ map handleCitationPart items case cs of @@ -660,7 +661,7 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList , ("eqref", rawInlineOr "eqref" $ doref "eqref") -- from amsmath.sty , ("mbox", rawInlineOr "mbox" $ processHBox <$> tok) , ("hbox", rawInlineOr "hbox" $ processHBox <$> tok) - , ("lettrine", rawInlineOr "lettrine" $ lettrine) + , ("lettrine", rawInlineOr "lettrine" lettrine) , ("(", mathInline . untokenize <$> manyTill anyTok (controlSeq ")")) , ("[", mathDisplay . untokenize <$> manyTill anyTok (controlSeq "]")) , ("ensuremath", mathInline . untokenize <$> braced) @@ -1073,7 +1074,7 @@ coloredInline stylename = do spanWith ("",[],[("style",stylename <> ": " <> untokenize color)]) <$> tok ttfamily :: PandocMonad m => LP m Inlines -ttfamily = (code . stringify . toList) <$> tok +ttfamily = code . stringify . toList <$> tok rawInlineOr :: PandocMonad m => Text -> LP m Inlines -> LP m Inlines rawInlineOr name' fallback = do @@ -1235,8 +1236,8 @@ doSubfile = do include :: (PandocMonad m, Monoid a) => Text -> LP m a include name = do skipMany opt - fs <- (map (T.unpack . removeDoubleQuotes . T.strip) . T.splitOn "," . - untokenize) <$> braced + fs <- map (T.unpack . removeDoubleQuotes . T.strip) . T.splitOn "," . + untokenize <$> braced let defaultExt | name == "usepackage" = ".sty" | otherwise = ".tex" mapM_ (insertIncluded defaultExt) fs @@ -1251,7 +1252,7 @@ insertIncluded defaultExtension f' = do ".tex" -> f' ".sty" -> f' _ -> addExtension f' defaultExtension - dirs <- (map T.unpack . splitTextBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS" + dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS" pos <- getPosition containers <- getIncludeFiles <$> getState when (T.pack f `elem` containers) $ @@ -1564,7 +1565,7 @@ blockCommands = M.fromList , ("frametitle", section nullAttr 3) , ("framesubtitle", section nullAttr 4) -- letters - , ("opening", (para . trimInlines) <$> (skipopts *> tok)) + , ("opening", para . trimInlines <$> (skipopts *> tok)) , ("closing", skipopts *> closing) -- memoir , ("plainbreak", braced >> pure horizontalRule) @@ -1578,10 +1579,10 @@ blockCommands = M.fromList -- , ("hrule", pure horizontalRule) , ("strut", pure mempty) - , ("rule", skipopts *> tok *> tok *> pure horizontalRule) + , ("rule", skipopts *> tok *> tok $> horizontalRule) , ("item", looseItem) , ("documentclass", skipopts *> braced *> preamble) - , ("centerline", (para . trimInlines) <$> (skipopts *> tok)) + , ("centerline", para . trimInlines <$> (skipopts *> tok)) , ("caption", mempty <$ setCaption) , ("bibliography", mempty <$ (skipopts *> braced >>= addMeta "bibliography" . splitBibs . untokenize)) @@ -1623,7 +1624,7 @@ environments :: PandocMonad m => M.Map Text (LP m Blocks) environments = M.fromList [ ("document", env "document" blocks <* skipMany anyTok) , ("abstract", mempty <$ (env "abstract" blocks >>= addMeta "abstract")) - , ("sloppypar", env "sloppypar" $ blocks) + , ("sloppypar", env "sloppypar" blocks) , ("letter", env "letter" letterContents) , ("minipage", env "minipage" $ skipopts *> spaces *> optional braced *> spaces *> blocks) @@ -1709,7 +1710,7 @@ proof = do bs <- env "proof" blocks return $ B.divWith ("", ["proof"], []) $ - addQed $ addTitle (B.emph (title <> ".")) $ bs + addQed $ addTitle (B.emph (title <> ".")) bs addTitle :: Inlines -> Blocks -> Blocks addTitle ils bs = @@ -1753,8 +1754,7 @@ theoremEnvironment name = do then do let name' = fromMaybe name $ theoremSeries tspec num <- getNextNumber - (fromMaybe (DottedNum [0]) . - fmap theoremLastNum . + (maybe (DottedNum [0]) theoremLastNum . M.lookup name' . sTheoremMap) updateState $ \s -> s{ sTheoremMap = @@ -1866,7 +1866,7 @@ inputMinted = do pos <- getPosition attr <- mintedAttr f <- T.filter (/='"') . untokenize <$> braced - dirs <- (map T.unpack . splitTextBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS" + dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS" mbCode <- readFileFromDirs dirs (T.unpack f) rawcode <- case mbCode of Just s -> return s @@ -1979,7 +1979,7 @@ inputListing = do pos <- getPosition options <- option [] keyvals f <- T.filter (/='"') . untokenize <$> braced - dirs <- (map T.unpack . splitTextBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS" + dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS" mbCode <- readFileFromDirs dirs (T.unpack f) codeLines <- case mbCode of Just s -> return $ T.lines s @@ -2176,18 +2176,17 @@ parseTableCell :: PandocMonad m => LP m Cell parseTableCell = do spaces updateState $ \st -> st{ sInTableCell = True } - cell' <- ( multicolumnCell + cell' <- multicolumnCell <|> multirowCell <|> parseSimpleCell <|> parseEmptyCell - ) updateState $ \st -> st{ sInTableCell = False } spaces return cell' where -- The parsing of empty cells is important in LaTeX, especially when dealing -- with multirow/multicolumn. See #6603. - parseEmptyCell = optional spaces >> return emptyCell <* optional spaces + parseEmptyCell = spaces $> emptyCell cellAlignment :: PandocMonad m => LP m Alignment cellAlignment = skipMany (symbol '|') *> alignment <* skipMany (symbol '|') @@ -2237,8 +2236,8 @@ multicolumnCell = controlSeq "multicolumn" >> do (Cell _ _ (RowSpan rs) _ bs) <- multirowCell return $ cell alignment - (RowSpan $ rs) - (ColSpan $ span') + (RowSpan rs) + (ColSpan span') (fromList bs) symbol '{' *> (nestedCell <|> singleCell) <* symbol '}' @@ -2276,7 +2275,7 @@ simpTable envname hasWidthParameter = try $ do lookAhead $ controlSeq "end" -- make sure we're at end return $ table emptyCaption (zip aligns widths) - (TableHead nullAttr $ header') + (TableHead nullAttr header') [TableBody nullAttr 0 [] rows] (TableFoot nullAttr []) diff --git a/src/Text/Pandoc/Readers/LaTeX/Lang.hs b/src/Text/Pandoc/Readers/LaTeX/Lang.hs index 55965c995..814b2fe79 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Lang.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Lang.hs @@ -152,4 +152,4 @@ babelLangToBCP47 s = "newzealand" -> Just $ Lang "en" "" "NZ" [] "american" -> Just $ Lang "en" "" "US" [] "classiclatin" -> Just $ Lang "la" "" "" ["x-classic"] - _ -> fmap ($ "") $ M.lookup s polyglossiaLangToBCP47 + _ -> ($ "") <$> M.lookup s polyglossiaLangToBCP47 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` ["-","+","@","|",":",","] diff --git a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs index 49a6d7301..436330d85 100644 --- a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs +++ b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs @@ -103,9 +103,9 @@ doSIang = do ps <- T.splitOn ";" . untokenize <$> braced case ps ++ repeat "" of (d:m:s:_) -> return $ - (if T.null d then mempty else (str d <> str "\xb0")) <> - (if T.null m then mempty else (str m <> str "\x2032")) <> - (if T.null s then mempty else (str s <> str "\x2033")) + (if T.null d then mempty else str d <> str "\xb0") <> + (if T.null m then mempty else str m <> str "\x2032") <> + (if T.null s then mempty else str s <> str "\x2033") _ -> return mempty -- converts e.g. \SIrange{100}{200}{\ms} to "100 ms--200 ms" diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs index 12001b534..ed31e1f9a 100644 --- a/src/Text/Pandoc/Readers/Man.hs +++ b/src/Text/Pandoc/Readers/Man.hs @@ -162,7 +162,7 @@ parseTable = do _ -> Nothing toRow = Row nullAttr . map simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] parseNewParagraph :: PandocMonad m => ManParser m Blocks parseNewParagraph = do diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 9b6671f1b..866b074c7 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1025,7 +1025,7 @@ htmlBlock = do guardEnabled Ext_raw_html try (do (TagOpen _ attrs) <- lookAhead $ fst <$> htmlTag isBlockTag - (return . B.rawBlock "html") <$> rawVerbatimBlock + return . B.rawBlock "html" <$> rawVerbatimBlock <|> (do guardEnabled Ext_markdown_attribute oldMarkdownAttribute <- stateMarkdownAttribute <$> getState markdownAttribute <- @@ -1582,7 +1582,7 @@ ender c n = try $ do three :: PandocMonad m => Char -> MarkdownParser m (F Inlines) three c = do contents <- mconcat <$> many (notFollowedBy (ender c 1) >> inline) - (ender c 3 >> updateLastStrPos >> return ((B.strong . B.emph) <$> contents)) + (ender c 3 >> updateLastStrPos >> return (B.strong . B.emph <$> contents)) <|> (ender c 2 >> updateLastStrPos >> one c (B.strong <$> contents)) <|> (ender c 1 >> updateLastStrPos >> two c (B.emph <$> contents)) <|> return (return (B.str $ T.pack [c,c,c]) <> contents) @@ -1617,7 +1617,7 @@ inlinesBetween :: PandocMonad m -> MarkdownParser m b -> MarkdownParser m (F Inlines) inlinesBetween start end = - (trimInlinesF . mconcat) <$> try (start >> many1Till inner end) + trimInlinesF . mconcat <$> try (start >> many1Till inner end) where inner = innerSpace <|> (notFollowedBy' (() <$ whitespace) >> inline) innerSpace = try $ whitespace <* notFollowedBy' end @@ -1720,7 +1720,7 @@ source = do try parenthesizedChars <|> (notFollowedBy (oneOf " )") >> countChar 1 litChar) <|> try (many1Char spaceChar <* notFollowedBy (oneOf "\"')")) - let sourceURL = (T.unwords . T.words . T.concat) <$> many urlChunk + let sourceURL = T.unwords . T.words . T.concat <$> many urlChunk let betweenAngles = try $ char '<' >> manyTillChar litChar (char '>') src <- try betweenAngles <|> sourceURL @@ -2023,7 +2023,7 @@ textualCite = try $ do mbrest <- option Nothing $ try $ spnl >> Just <$> withRaw normalCite case mbrest of Just (rest, raw) -> - return $ (flip B.cite (B.text $ "@" <> key <> " " <> raw) . (first:)) + return $ flip B.cite (B.text $ "@" <> key <> " " <> raw) . (first:) <$> rest Nothing -> (do @@ -2130,4 +2130,4 @@ toRow :: [Blocks] -> Row toRow = Row nullAttr . map B.simpleCell toHeaderRow :: [Blocks] -> [Row] -toHeaderRow l = if null l then [] else [toRow l] +toHeaderRow l = [toRow l | not (null l)] diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index bcf1228ad..6e7dc3110 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -231,7 +231,7 @@ table = do then (hdr, rows') else (replicate cols mempty, hdr:rows') let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.table (B.simpleCaption $ B.plain caption) cellspecs (TableHead nullAttr $ toHeaderRow headers) @@ -283,7 +283,7 @@ tableCaption = try $ do skipSpaces sym "|+" optional (try $ parseAttrs *> skipSpaces *> char '|' *> blanklines) - (trimInlines . mconcat) <$> + trimInlines . mconcat <$> many (notFollowedBy (cellsep <|> rowsep) *> inline) tableRow :: PandocMonad m => MWParser m [((Alignment, Double), Blocks)] @@ -678,7 +678,7 @@ url = do -- | Parses a list of inlines between start and end delimiters. inlinesBetween :: (PandocMonad m, Show b) => MWParser m a -> MWParser m b -> MWParser m Inlines inlinesBetween start end = - (trimInlines . mconcat) <$> try (start >> many1Till inner end) + trimInlines . mconcat <$> try (start >> many1Till inner end) where inner = innerSpace <|> (notFollowedBy' (() <$ whitespace) >> inline) innerSpace = try $ whitespace <* notFollowedBy' end diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs index 751a37808..b4eea9d3a 100644 --- a/src/Text/Pandoc/Readers/Muse.hs +++ b/src/Text/Pandoc/Readers/Muse.hs @@ -653,7 +653,7 @@ museToPandocTable (MuseTable caption headers body footers) = where attrs = (AlignDefault, ColWidthDefault) <$ transpose (headers ++ body ++ footers) (headRow, rows) = fromMaybe ([], []) $ uncons headers toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] museAppendElement :: MuseTableElement -> MuseTable diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 74120f96a..24391dbf0 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -220,9 +220,9 @@ uniqueIdentFrom :: AnchorPrefix -> [Anchor] -> Anchor uniqueIdentFrom baseIdent usedIdents = let numIdent n = baseIdent <> "-" <> T.pack (show n) in if baseIdent `elem` usedIdents - then case find (\x -> numIdent x `notElem` usedIdents) ([1..60000] :: [Int]) of - Just x -> numIdent x - Nothing -> baseIdent -- if we have more than 60,000, allow repeats + then maybe baseIdent numIdent + $ find (\x -> numIdent x `notElem` usedIdents) ([1..60000] :: [Int]) + -- if we have more than 60,000, allow repeats else baseIdent -- | First argument: basis for a new "pretty" anchor if none exists yet diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs index 5583d64ce..00c636a0d 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs @@ -1,5 +1,6 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternGuards #-} {- | Module : Text.Pandoc.Readers.Odt.Generic.XMLConverter @@ -691,7 +692,7 @@ makeMatcherC nsID name c = ( second ( contentToElem >>% recover) &&&^ snd contentToElem :: FallibleXMLConverter nsID extraState XML.Content XML.Element - contentToElem = arr $ \e -> case e of + contentToElem = arr $ \case XML.Elem e' -> succeedWith e' _ -> failEmpty diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index c60817d1b..d71cd7faf 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Shared (compactify, compactifyDL, safeRead) import Control.Monad (foldM, guard, mplus, mzero, void) import Data.Char (isSpace) import Data.Default (Default) +import Data.Functor (($>)) import Data.List (foldl', intersperse) import Data.Maybe (fromMaybe, isJust, isNothing) import Data.Text (Text) @@ -103,9 +104,7 @@ attrFromBlockAttributes :: BlockAttributes -> Attr attrFromBlockAttributes BlockAttributes{..} = let ident = fromMaybe mempty $ lookup "id" blockAttrKeyValues - classes = case lookup "class" blockAttrKeyValues of - Nothing -> [] - Just clsStr -> T.words clsStr + classes = maybe [] T.words $ lookup "class" blockAttrKeyValues kv = filter ((`notElem` ["id", "class"]) . fst) blockAttrKeyValues in (ident, classes, kv) @@ -576,10 +575,10 @@ rawExportLine = try $ do rawOrgLine :: PandocMonad m => OrgParser m (F Blocks) rawOrgLine = do line <- metaLineStart *> anyLine - returnF $ B.rawBlock "org" $ ("#+" <> line) + returnF $ B.rawBlock "org" $ "#+" <> line commentLine :: Monad m => OrgParser m Blocks -commentLine = commentLineStart *> anyLine *> pure mempty +commentLine = commentLineStart *> anyLine $> mempty -- @@ -648,12 +647,12 @@ orgToPandocTable (OrgTable colProps heads lns) caption = (TableFoot nullAttr []) where toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth) convertColProp totalWidth colProp = let align' = fromMaybe AlignDefault $ columnAlignment colProp - width' = (\w t -> (fromIntegral w / fromIntegral t)) + width' = (\w t -> fromIntegral w / fromIntegral t) <$> columnRelWidth colProp <*> totalWidth in (align', maybe ColWidthDefault ColWidth width') @@ -691,9 +690,9 @@ columnPropertyCell = emptyOrgCell <|> propCell <?> "alignment info" tableAlignFromChar :: Monad m => OrgParser m Alignment tableAlignFromChar = try $ - choice [ char 'l' *> return AlignLeft - , char 'c' *> return AlignCenter - , char 'r' *> return AlignRight + choice [ char 'l' $> AlignLeft + , char 'c' $> AlignCenter + , char 'r' $> AlignRight ] tableHline :: Monad m => OrgParser m OrgTableRow @@ -796,13 +795,13 @@ paraOrPlain = try $ do -- Make sure we are not looking at a headline notFollowedBy' headerStart ils <- inlines - nl <- option False (newline *> return True) + nl <- option False (newline $> True) -- Read block as paragraph, except if we are in a list context and the block -- is directly followed by a list item, in which case the block is read as -- plain text. try (guard nl *> notFollowedBy (inList *> (orderedListStart <|> bulletListStart)) - *> return (B.para <$> ils)) + $> (B.para <$> ils)) <|> return (B.plain <$> ils) diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 6e2e86373..1e4799e7b 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -122,7 +122,7 @@ data OrgParserState = OrgParserState , orgMacros :: M.Map Text Macro } -data OrgParserLocal = OrgParserLocal +newtype OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext } diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index 3934be6e1..7f72077a4 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -58,9 +58,7 @@ cleanLinkText s originalLang :: Text -> [(Text, Text)] originalLang lang = let transLang = translateLang lang - in if transLang == lang - then [] - else [("org-language", lang)] + in [("org-language", lang) | transLang /= lang] -- | Translate from Org-mode's programming language identifiers to those used -- by Pandoc. This is useful to allow for proper syntax highlighting in diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 25682a500..50947c1be 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -164,7 +164,7 @@ parseRST = do , stateIdentifiers = mempty } -- now parse it for real... blocks <- B.toList <$> parseBlocks - citations <- (sort . M.toList . stateCitations) <$> getState + citations <- sort . M.toList . stateCitations <$> getState citationItems <- mapM parseCitation citations let refBlock = [Div ("citations",[],[]) $ B.toList $ B.definitionList citationItems | not (null citationItems)] @@ -823,7 +823,7 @@ listTableDirective top fields body = do splitTextBy (`elem` (" ," :: String)) specs _ -> replicate numOfCols ColWidthDefault toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.table (B.simpleCaption $ B.plain title) (zip (replicate numOfCols AlignDefault) widths) (TableHead nullAttr $ toHeaderRow headerRow) @@ -906,7 +906,7 @@ csvTableDirective top fields rawcsv = do $ splitTextBy (`elem` (" ," :: String)) specs _ -> replicate numOfCols ColWidthDefault let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.table (B.simpleCaption $ B.plain title) (zip (replicate numOfCols AlignDefault) widths) (TableHead nullAttr $ toHeaderRow headerRow) @@ -1014,7 +1014,7 @@ toChunks = dropWhile T.null codeblock :: Text -> [Text] -> [(Text, Text)] -> Text -> Text -> Bool -> RSTParser m Blocks -codeblock ident classes fields lang body rmTrailingNewlines = do +codeblock ident classes fields lang body rmTrailingNewlines = return $ B.codeBlockWith attribs $ stripTrailingNewlines' body where stripTrailingNewlines' = if rmTrailingNewlines then stripTrailingNewlines diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index ebd87359a..484a6c923 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -214,7 +214,7 @@ listItemLine prefix marker = mconcat <$> (lineContent >>= parseContent) listContinuation = notFollowedBy (textStr prefix >> marker) >> string " " >> lineContent parseContent = parseFromString' $ many1 $ nestedList <|> parseInline - parseInline = (B.plain . mconcat) <$> many1Till inline (lastNewline <|> newlineBeforeNestedList) + parseInline = B.plain . mconcat <$> many1Till inline (lastNewline <|> newlineBeforeNestedList) nestedList = list prefix lastNewline = try $ char '\n' <* eof newlineBeforeNestedList = try $ char '\n' <* lookAhead nestedList @@ -235,7 +235,7 @@ table = try $ do columns rows = replicate (columCount rows) mempty columCount rows = length $ head rows toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] tableParseHeader :: PandocMonad m => TWParser m ((Alignment, ColWidth), B.Blocks) tableParseHeader = try $ do @@ -265,13 +265,13 @@ tableEndOfRow :: PandocMonad m => TWParser m Char tableEndOfRow = lookAhead (try $ char '|' >> char '\n') >> char '|' tableColumnContent :: PandocMonad m => TWParser m a -> TWParser m B.Blocks -tableColumnContent end = (B.plain . mconcat) <$> manyTill content (lookAhead $ try end) +tableColumnContent end = B.plain . mconcat <$> manyTill content (lookAhead $ try end) where content = continuation <|> inline continuation = try $ char '\\' >> newline >> return mempty blockQuote :: PandocMonad m => TWParser m B.Blocks -blockQuote = (B.blockQuote . mconcat) <$> parseHtmlContent "blockquote" block +blockQuote = B.blockQuote . mconcat <$> parseHtmlContent "blockquote" block noautolink :: PandocMonad m => TWParser m B.Blocks noautolink = do @@ -285,7 +285,7 @@ noautolink = do parseContent = parseFromString' $ many block para :: PandocMonad m => TWParser m B.Blocks -para = (result . mconcat) <$> many1Till inline endOfParaElement +para = result . mconcat <$> many1Till inline endOfParaElement where endOfParaElement = lookAhead $ endOfInput <|> endOfPara <|> newBlockElement endOfInput = try $ skipMany blankline >> skipSpaces >> eof @@ -428,13 +428,13 @@ nestedString end = innerSpace <|> countChar 1 nonspaceChar innerSpace = try $ many1Char spaceChar <* notFollowedBy end boldCode :: PandocMonad m => TWParser m B.Inlines -boldCode = try $ (B.strong . B.code . fromEntities) <$> enclosed (string "==") nestedString +boldCode = try $ B.strong . B.code . fromEntities <$> enclosed (string "==") nestedString htmlComment :: PandocMonad m => TWParser m B.Inlines htmlComment = htmlTag isCommentTag >> return mempty code :: PandocMonad m => TWParser m B.Inlines -code = try $ (B.code . fromEntities) <$> enclosed (char '=') nestedString +code = try $ B.code . fromEntities <$> enclosed (char '=') nestedString codeHtml :: PandocMonad m => TWParser m B.Inlines codeHtml = do diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index b105b587d..6691d8381 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -282,7 +282,7 @@ definitionListStart = try $ do -- break. definitionListItem :: PandocMonad m => ParserT Text ParserState m (Inlines, [Blocks]) definitionListItem = try $ do - term <- (mconcat . intersperse B.linebreak) <$> many1 definitionListStart + term <- mconcat . intersperse B.linebreak <$> many1 definitionListStart def' <- string ":=" *> optional whitespace *> (multilineDef <|> inlineDef) return (term, def') where inlineDef :: PandocMonad m => ParserT Text ParserState m [Blocks] @@ -378,7 +378,7 @@ table = try $ do let nbOfCols = maximum $ map length (headers:rows) let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows) let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.table (B.simpleCaption $ B.plain caption) (zip aligns (replicate nbOfCols ColWidthDefault)) (TableHead nullAttr $ toHeaderRow $ map snd headers) @@ -439,7 +439,7 @@ inlineParsers = [ str , link , image , mark - , (B.str . T.singleton) <$> characterReference + , B.str . T.singleton <$> characterReference , smartPunctuation inline , symbol ] diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 245df6f08..5c5b3c4e9 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -267,7 +267,7 @@ table = try $ do let rowsPadded = map (pad size) rows' let headerPadded = if null tableHeader then mempty else pad size tableHeader let toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] return $ B.table B.emptyCaption (zip aligns (replicate ncolumns ColWidthDefault)) (TableHead nullAttr $ toHeaderRow headerPadded) diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 9a293d2ab..4853621c8 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -580,7 +580,7 @@ makeSections numbering mbBaseLevel bs = let kvs' = -- don't touch number if already present case lookup "number" kvs of Nothing | numbering - , not ("unnumbered" `elem` classes) -> + , "unnumbered" `notElem` classes -> ("number", T.intercalate "." (map tshow newnum)) : kvs _ -> kvs let divattr = (ident, "section":classes, kvs') @@ -626,11 +626,9 @@ headerLtEq _ _ = False uniqueIdent :: Extensions -> [Inline] -> Set.Set T.Text -> T.Text uniqueIdent exts title' usedIdents = if baseIdent `Set.member` usedIdents - then case find (\x -> numIdent x `Set.notMember` usedIdents) - ([1..60000] :: [Int]) of - Just x -> numIdent x - Nothing -> baseIdent - -- if we have more than 60,000, allow repeats + then maybe baseIdent numIdent + $ find (\x -> numIdent x `Set.notMember` usedIdents) ([1..60000] :: [Int]) + -- if we have more than 60,000, allow repeats else baseIdent where baseIdent = case inlineListToIdentifier exts title' of diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index e991cd384..66ded218f 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -1,5 +1,3 @@ -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.CommonMark Copyright : Copyright (C) 2015-2020 John MacFarlane diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 7bae37a79..0a6313513 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -209,7 +209,7 @@ blockToConTeXt (Div (ident,_,kvs) bs) = do <> literal lng <> "]" $$ txt $$ "\\stop" Nothing -> txt wrapBlank txt = blankline <> txt <> blankline - (wrapBlank . wrapLang . wrapDir . wrapRef) <$> blockListToConTeXt bs + wrapBlank . wrapLang . wrapDir . wrapRef <$> blockListToConTeXt bs blockToConTeXt (BulletList lst) = do contents <- mapM listItemToConTeXt lst return $ ("\\startitemize" <> if isTightList lst @@ -332,7 +332,7 @@ alignToConTeXt align = case align of AlignDefault -> empty listItemToConTeXt :: PandocMonad m => [Block] -> WM m (Doc Text) -listItemToConTeXt list = (("\\item" $$) . nest 2) <$> blockListToConTeXt list +listItemToConTeXt list = ("\\item" $$) . nest 2 <$> blockListToConTeXt list defListItemToConTeXt :: PandocMonad m => ([Inline], [[Block]]) -> WM m (Doc Text) defListItemToConTeXt (term, defs) = do @@ -487,7 +487,7 @@ inlineToConTeXt (Span (_,_,kvs) ils) = do Just lng -> braces ("\\language" <> brackets (literal lng) <> txt) Nothing -> txt - (wrapLang . wrapDir) <$> inlineListToConTeXt ils + wrapLang . wrapDir <$> inlineListToConTeXt ils -- | Craft the section header, inserting the section reference, if supplied. sectionHeader :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index d3517159f..408d8cc0c 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -179,7 +179,7 @@ blockToDocbook opts (Div (id',"section":_,_) (Header lvl _ ils : xs)) = do blockToDocbook opts (Div (ident,_,_) [Para lst]) = let attribs = [("id", ident) | not (T.null ident)] in if hasLineBreaks lst - then (flush . nowrap . inTags False "literallayout" attribs) + then flush . nowrap . inTags False "literallayout" attribs <$> inlinesToDocbook opts lst else inTags True "para" attribs <$> inlinesToDocbook opts lst blockToDocbook opts (Div (ident,_,_) bs) = do @@ -206,7 +206,7 @@ blockToDocbook opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just _)]) (imageToDocbook opts attr src) $$ inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToDocbook opts (Para lst) - | hasLineBreaks lst = (flush . nowrap . inTagsSimple "literallayout") + | hasLineBreaks lst = flush . nowrap . inTagsSimple "literallayout" <$> inlinesToDocbook opts lst | otherwise = inTagsIndented "para" <$> inlinesToDocbook opts lst blockToDocbook opts (LineBlock lns) = @@ -277,7 +277,7 @@ blockToDocbook opts (Table _ blkCapt specs thead tbody tfoot) = do head' <- if all null headers then return empty else inTagsIndented "thead" <$> tableRowToDocbook opts headers - body' <- (inTagsIndented "tbody" . vcat) <$> + body' <- inTagsIndented "tbody" . vcat <$> mapM (tableRowToDocbook opts) rows return $ inTagsIndented tableType $ captionDoc $$ inTags True "tgroup" [("cols", tshow (length aligns))] ( @@ -305,14 +305,14 @@ tableRowToDocbook :: PandocMonad m -> [[Block]] -> DB m (Doc Text) tableRowToDocbook opts cols = - (inTagsIndented "row" . vcat) <$> mapM (tableItemToDocbook opts) cols + inTagsIndented "row" . vcat <$> mapM (tableItemToDocbook opts) cols tableItemToDocbook :: PandocMonad m => WriterOptions -> [Block] -> DB m (Doc Text) tableItemToDocbook opts item = - (inTags True "entry" [] . vcat) <$> mapM (blockToDocbook opts) item + inTags True "entry" [] . vcat <$> mapM (blockToDocbook opts) item -- | Convert a list of inline elements to Docbook. inlinesToDocbook :: PandocMonad m => WriterOptions -> [Inline] -> DB m (Doc Text) diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 81dbb6ce0..fa7e2ceea 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1030,7 +1030,7 @@ blockToOpenXML' opts (Table _ blkCapt specs thead tbody tfoot) = do let rowwidth = fullrow * sum widths let mkgridcol w = mknode "w:gridCol" [("w:w", show (floor (textwidth * w) :: Integer))] () - let hasHeader = any (not . null) headers + let hasHeader = not $ all null headers modify $ \s -> s { stInTable = False } return $ caption' ++ diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 63034a577..12004889f 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -62,7 +62,7 @@ import Text.DocTemplates (FromContext(lookupContext), Context(..), ToContext(toVal), Val(..)) -- A Chapter includes a list of blocks. -data Chapter = Chapter [Block] +newtype Chapter = Chapter [Block] deriving (Show) data EPUBState = EPUBState { @@ -711,10 +711,10 @@ pandocToEPUB version opts doc = do | writerTableOfContents opts ] ++ map chapterRefNode chapterEntries) , unode "guide" $ - [ unode "reference" ! - [("type","toc"),("title", tocTitle), - ("href","nav.xhtml")] $ () - ] ++ + (unode "reference" ! + [("type","toc"),("title", tocTitle), + ("href","nav.xhtml")] $ () + ) : [ unode "reference" ! [("type","cover") ,("title","Cover") @@ -838,14 +838,12 @@ pandocToEPUB version opts doc = do ] | writerTableOfContents opts ] else [] - let landmarks = if null landmarkItems - then [] - else [RawBlock (Format "html") $ TS.pack $ ppElement $ - unode "nav" ! [("epub:type","landmarks") - ,("id","landmarks") - ,("hidden","hidden")] $ - [ unode "ol" landmarkItems ] - ] + let landmarks = [RawBlock (Format "html") $ TS.pack $ ppElement $ + unode "nav" ! [("epub:type","landmarks") + ,("id","landmarks") + ,("hidden","hidden")] $ + [ unode "ol" landmarkItems ] + | not (null landmarkItems)] navData <- lift $ writeHtml opts'{ writerVariables = Context (M.fromList [("navpage", toVal' "true")]) <> cssvars False <> vars } @@ -940,7 +938,7 @@ metadataElement version md currentTime = | version == EPUB2 = [dcNode "identifier" ! (("id",id') : maybe [] (\x -> [("opf:scheme", x)]) scheme) $ txt] - | otherwise = [dcNode "identifier" ! [("id",id')] $ txt] ++ + | otherwise = (dcNode "identifier" ! [("id",id')] $ txt) : maybe [] ((\x -> [unode "meta" ! [ ("refines",'#':id') , ("property","identifier-type") diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 6bb708c37..decc487c1 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} @@ -1025,7 +1024,7 @@ rowListToHtml :: PandocMonad m -> [TableRow] -> StateT WriterState m Html rowListToHtml opts rows = - (\x -> (nl opts *> mconcat x)) <$> + (\x -> nl opts *> mconcat x) <$> mapM (tableRowToHtml opts) rows colSpecListToHtml :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 9d8c5ec41..aaa19ed07 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -28,7 +28,7 @@ import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared type Notes = [[Block]] -data WriterState = WriterState { stNotes :: Notes } +newtype WriterState = WriterState { stNotes :: Notes } instance Default WriterState where def = WriterState{ stNotes = [] } diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 50ce04e03..4dc02d686 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -216,7 +216,7 @@ imageMimeType src kvs = (T.takeWhile (/='/') <$> mbMT) subtype = fromMaybe "" $ lookup "mime-subtype" kvs `mplus` - ((T.drop 1 . T.dropWhile (/='/')) <$> mbMT) + (T.drop 1 . T.dropWhile (/='/') <$> mbMT) in (maintype, subtype) languageFor :: [Text] -> Text @@ -372,7 +372,7 @@ blockToJATS opts (Table _ blkCapt specs th tb tf) = thead <- if all null headers then return empty else inTagsIndented "thead" <$> tableRowToJATS opts True headers - tbody <- (inTagsIndented "tbody" . vcat) <$> + tbody <- inTagsIndented "tbody" . vcat <$> mapM (tableRowToJATS opts False) rows return $ inTags True "table" [] $ coltags $$ thead $$ tbody @@ -389,7 +389,7 @@ tableRowToJATS :: PandocMonad m -> [[Block]] -> JATS m (Doc Text) tableRowToJATS opts isHeader cols = - (inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols + inTagsIndented "tr" . vcat <$> mapM (tableItemToJATS opts isHeader) cols tableItemToJATS :: PandocMonad m => WriterOptions @@ -400,7 +400,7 @@ tableItemToJATS opts isHeader [Plain item] = inTags False (if isHeader then "th" else "td") [] <$> inlinesToJATS opts item tableItemToJATS opts isHeader item = - (inTags False (if isHeader then "th" else "td") [] . vcat) <$> + inTags False (if isHeader then "th" else "td") [] . vcat <$> mapM (blockToJATS opts) item -- | Convert a list of inline elements to JATS. @@ -547,7 +547,7 @@ inlineToJATS _ (Image (ident,_,kvs) _ (src, tit)) = do (T.takeWhile (/='/') <$> mbMT) let subtype = fromMaybe "" $ lookup "mime-subtype" kvs `mplus` - ((T.drop 1 . T.dropWhile (/='/')) <$> mbMT) + (T.drop 1 . T.dropWhile (/='/') <$> mbMT) let attr = [("id", ident) | not (T.null ident)] ++ [("mimetype", maintype), ("mime-subtype", subtype), diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 3753604db..071a288e1 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -1049,7 +1049,7 @@ wrapDiv (_,classes,kvs) t = do let valign = maybe "T" mapAlignment (lookup "align" kvs) totalwidth = maybe [] (\x -> ["totalwidth=" <> x]) (lookup "totalwidth" kvs) - onlytextwidth = filter ((==) "onlytextwidth") classes + onlytextwidth = filter ("onlytextwidth" ==) classes options = text $ T.unpack $ T.intercalate "," $ valign : totalwidth ++ onlytextwidth in inCmd "begin" "columns" <> brackets options @@ -1458,8 +1458,8 @@ citeArgumentsList (CiteGroup _ _ []) = return empty citeArgumentsList (CiteGroup pfxs sfxs ids) = do pdoc <- inlineListToLaTeX pfxs sdoc <- inlineListToLaTeX sfxs' - return $ (optargs pdoc sdoc) <> - (braces (literal (T.intercalate "," (reverse ids)))) + return $ optargs pdoc sdoc <> + braces (literal (T.intercalate "," (reverse ids))) where sfxs' = stripLocatorBraces $ case sfxs of (Str t : r) -> case T.uncons t of Just (x, xs) @@ -1516,12 +1516,12 @@ citationsToBiblatex (c:cs) groups <- mapM citeArgumentsList (reverse (foldl' grouper [] (c:cs))) - return $ text cmd <> (mconcat groups) + return $ text cmd <> mconcat groups where grouper prev cit = case prev of ((CiteGroup oPfx oSfx ids):rest) - | null oSfx && null pfx -> (CiteGroup oPfx sfx (cid:ids)):rest - _ -> (CiteGroup pfx sfx [cid]):prev + | null oSfx && null pfx -> CiteGroup oPfx sfx (cid:ids) : rest + _ -> CiteGroup pfx sfx [cid] : prev where pfx = citationPrefix cit sfx = citationSuffix cit cid = citationId cit diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 62449431c..4eb0db042 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} {- | @@ -232,8 +233,7 @@ definitionListItemToMan opts (label, defs) = do labelText <- inlineListToMan opts $ makeCodeBold label contents <- if null defs then return empty - else liftM vcat $ forM defs $ \blocks -> - case blocks of + else liftM vcat $ forM defs $ \case (x:xs) -> do first' <- blockToMan opts $ case x of diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3e50704ca..323d159b0 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -24,10 +24,9 @@ import Control.Monad.Reader import Control.Monad.State.Strict import Data.Char (isAlphaNum) import Data.Default -import Data.List (find, intersperse, sortBy, transpose) +import Data.List (find, intersperse, sortOn, transpose) import qualified Data.Map as M import Data.Maybe (fromMaybe, mapMaybe) -import Data.Ord (comparing) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T @@ -127,7 +126,7 @@ pandocTitleBlock tit auths dat = mmdTitleBlock :: Context Text -> Doc Text mmdTitleBlock (Context hashmap) = - vcat $ map go $ sortBy (comparing fst) $ M.toList hashmap + vcat $ map go $ sortOn fst $ M.toList hashmap where go (k,v) = case (text (T.unpack k), v) of (k', ListVal xs) @@ -148,15 +147,15 @@ mmdTitleBlock (Context hashmap) = plainTitleBlock :: Doc Text -> [Doc Text] -> Doc Text -> Doc Text plainTitleBlock tit auths dat = tit <> cr <> - (hcat (intersperse (text "; ") auths)) <> cr <> + hcat (intersperse (text "; ") auths) <> cr <> dat <> cr yamlMetadataBlock :: Context Text -> Doc Text -yamlMetadataBlock v = "---" $$ (contextToYaml v) $$ "---" +yamlMetadataBlock v = "---" $$ contextToYaml v $$ "---" contextToYaml :: Context Text -> Doc Text contextToYaml (Context o) = - vcat $ map keyvalToYaml $ sortBy (comparing fst) $ M.toList o + vcat $ map keyvalToYaml $ sortOn fst $ M.toList o where keyvalToYaml (k,v) = case (text (T.unpack k), v) of @@ -250,7 +249,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do -- | Return markdown representation of reference key table. refsToMarkdown :: PandocMonad m => WriterOptions -> Refs -> MD m (Doc Text) -refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat +refsToMarkdown opts refs = vcat <$> mapM (keyToMarkdown opts) refs -- | Return markdown representation of a reference key. keyToMarkdown :: PandocMonad m @@ -446,7 +445,7 @@ blockToMarkdown' opts (Plain inlines) = do then inlines else case inlines of (Str t:ys) - | (null ys || startsWithSpace ys) + | null ys || startsWithSpace ys , beginsWithOrderedListMarker t -> RawInline (Format "markdown") (escapeMarker t):ys (Str t:_) @@ -462,7 +461,7 @@ blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Ju | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts) && attr /= nullAttr = -- use raw HTML - ((<> blankline) . literal . T.strip) <$> + (<> blankline) . literal . T.strip <$> writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [Para [Image attr alt (src,tgt)]]) | otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)]) @@ -472,7 +471,7 @@ blockToMarkdown' opts (LineBlock lns) = if isEnabled Ext_line_blocks opts then do mdLines <- mapM (inlineListToMarkdown opts) lns - return $ (vcat $ map (hang 2 (literal "| ")) mdLines) <> blankline + return $ vcat (map (hang 2 (literal "| ")) mdLines) <> blankline else blockToMarkdown opts $ linesToPara lns blockToMarkdown' opts b@(RawBlock f str) = do variant <- asks envVariant @@ -582,28 +581,28 @@ blockToMarkdown' opts (CodeBlock attribs str) = do attrs = if isEnabled Ext_fenced_code_attributes opts then nowrap $ " " <> attrsToMarkdown attribs else case attribs of - (_,(cls:_),_) -> " " <> literal cls + (_,cls:_,_) -> " " <> literal cls _ -> empty blockToMarkdown' opts (BlockQuote blocks) = do variant <- asks envVariant -- if we're writing literate haskell, put a space before the bird tracks -- so they won't be interpreted as lhs... - let leader = if isEnabled Ext_literate_haskell opts - then " > " - else if variant == PlainText then " " else "> " + let leader + | isEnabled Ext_literate_haskell opts = " > " + | variant == PlainText = " " + | otherwise = "> " contents <- blockListToMarkdown opts blocks - return $ (prefixed leader contents) <> blankline + return $ prefixed leader contents <> blankline blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot let numcols = maximum (length aligns : length widths : map length (headers:rows)) caption' <- inlineListToMarkdown opts caption - let caption'' = if null caption - then blankline - else - if isEnabled Ext_table_captions opts - then blankline $$ (": " <> caption') $$ blankline - else blankline $$ caption' $$ blankline + let caption'' + | null caption = blankline + | isEnabled Ext_table_captions opts + = blankline $$ (": " <> caption') $$ blankline + | otherwise = blankline $$ caption' $$ blankline let hasSimpleCells = onlySimpleTableCells $ headers : rows let isSimple = hasSimpleCells && all (==0) widths let isPlainBlock (Plain _) = True @@ -652,7 +651,7 @@ blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do (id,) <$> pipeTable (all null headers) aligns' rawHeaders rawRows | isEnabled Ext_raw_html opts -> fmap (id,) $ literal <$> - (writeHtml5String opts{ writerTemplate = Nothing } $ Pandoc nullMeta [t]) + writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [t]) | otherwise -> return (id, literal "[TABLE]") return $ nst (tbl $$ caption'') $$ blankline blockToMarkdown' opts (BulletList items) = do @@ -680,7 +679,7 @@ inList p = local (\env -> env {envInList = True}) p addMarkdownAttribute :: Text -> Text addMarkdownAttribute s = case span isTagText $ reverse $ parseTags s of - (xs,(TagOpen t attrs:rest)) -> + (xs, TagOpen t attrs:rest) -> renderTags' $ reverse rest ++ (TagOpen t attrs' : reverse xs) where attrs' = ("markdown","1"):[(x,y) | (x,y) <- attrs, x /= "markdown"] @@ -745,17 +744,16 @@ pandocTable opts multiline headless aligns widths rawHeaders rawRows = do | isSimple = map numChars columns | otherwise = zipWith relWidth widths columns let makeRow = hcat . intersperse (lblock 1 (literal " ")) . - (zipWith3 alignHeader aligns widthsInChars) + zipWith3 alignHeader aligns widthsInChars let rows' = map makeRow rawRows let head' = makeRow rawHeaders let underline = mconcat $ intersperse (literal " ") $ map (\width -> literal (T.replicate width "-")) widthsInChars - let border = if multiline - then literal (T.replicate (sum widthsInChars + - length widthsInChars - 1) "-") - else if headless - then underline - else empty + let border + | multiline = literal (T.replicate (sum widthsInChars + + length widthsInChars - 1) "-") + | headless = underline + | otherwise = empty let head'' = if headless then empty else border <> cr <> head' @@ -890,18 +888,17 @@ blockListToMarkdown opts blocks = do isListBlock (OrderedList _ _) = True isListBlock (DefinitionList _) = True isListBlock _ = False - commentSep = if variant == PlainText - then Null - else if isEnabled Ext_raw_html opts - then RawBlock "html" "<!-- -->\n" - else RawBlock "markdown" " \n" - mapM (blockToMarkdown opts) (fixBlocks blocks) >>= return . mconcat + commentSep + | variant == PlainText = Null + | isEnabled Ext_raw_html opts = RawBlock "html" "<!-- -->\n" + | otherwise = RawBlock "markdown" " \n" + mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks) getKey :: Doc Text -> Key getKey = toKey . render Nothing findUsableIndex :: [Text] -> Int -> Int -findUsableIndex lbls i = if (tshow i) `elem` lbls +findUsableIndex lbls i = if tshow i `elem` lbls then findUsableIndex lbls (i + 1) else i @@ -973,19 +970,19 @@ inlineListToMarkdown opts lst = do go (if inlist then avoidBadWrapsInList lst else lst) where go [] = return empty go (i:is) = case i of - (Link _ _ _) -> case is of + Link {} -> case is of -- If a link is followed by another link, or '[', '(' or ':' -- then we don't shortcut - (Link _ _ _):_ -> unshortcutable - Space:(Link _ _ _):_ -> unshortcutable + Link {}:_ -> unshortcutable + Space:Link {}:_ -> unshortcutable Space:(Str(thead -> Just '[')):_ -> unshortcutable Space:(RawInline _ (thead -> Just '[')):_ -> unshortcutable Space:(Cite _ _):_ -> unshortcutable - SoftBreak:(Link _ _ _):_ -> unshortcutable + SoftBreak:Link {}:_ -> unshortcutable SoftBreak:(Str(thead -> Just '[')):_ -> unshortcutable SoftBreak:(RawInline _ (thead -> Just '[')):_ -> unshortcutable SoftBreak:(Cite _ _):_ -> unshortcutable - LineBreak:(Link _ _ _):_ -> unshortcutable + LineBreak:Link {}:_ -> unshortcutable LineBreak:(Str(thead -> Just '[')):_ -> unshortcutable LineBreak:(RawInline _ (thead -> Just '[')):_ -> unshortcutable LineBreak:(Cite _ _):_ -> unshortcutable @@ -1016,16 +1013,16 @@ avoidBadWrapsInList :: [Inline] -> [Inline] avoidBadWrapsInList [] = [] avoidBadWrapsInList (s:Str (T.uncons -> Just ('>',cs)):xs) | isSp s = Str (" >" <> cs) : avoidBadWrapsInList xs -avoidBadWrapsInList (s:Str (T.uncons -> Just (c, cs)):[]) - | T.null cs && isSp s && c `elem` ['-','*','+'] = Str (T.pack [' ', c]) : [] +avoidBadWrapsInList [s, Str (T.uncons -> Just (c, cs))] + | T.null cs && isSp s && c `elem` ['-','*','+'] = [Str $ T.pack [' ', c]] avoidBadWrapsInList (s:Str (T.uncons -> Just (c, cs)):Space:xs) | T.null cs && isSp s && c `elem` ['-','*','+'] = Str (T.pack [' ', c]) : Space : avoidBadWrapsInList xs avoidBadWrapsInList (s:Str cs:Space:xs) | isSp s && isOrderedListMarker cs = Str (" " <> cs) : Space : avoidBadWrapsInList xs -avoidBadWrapsInList (s:Str cs:[]) - | isSp s && isOrderedListMarker cs = Str (" " <> cs) : [] +avoidBadWrapsInList [s, Str cs] + | isSp s && isOrderedListMarker cs = [Str $ " " <> cs] avoidBadWrapsInList (x:xs) = x : avoidBadWrapsInList xs isOrderedListMarker :: Text -> Bool @@ -1105,7 +1102,7 @@ inlineToMarkdown opts (Strikeout lst) = do else contents inlineToMarkdown _ (Superscript []) = return empty inlineToMarkdown opts (Superscript lst) = - local (\env -> env {envEscapeSpaces = (envVariant env == Markdown)}) $ do + local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do contents <- inlineListToMarkdown opts lst if isEnabled Ext_superscript opts then return $ "^" <> contents <> "^" @@ -1123,7 +1120,7 @@ inlineToMarkdown opts (Superscript lst) = Nothing -> literal $ "^(" <> rendered <> ")" inlineToMarkdown _ (Subscript []) = return empty inlineToMarkdown opts (Subscript lst) = - local (\env -> env {envEscapeSpaces = (envVariant env == Markdown)}) $ do + local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do contents <- inlineListToMarkdown opts lst if isEnabled Ext_subscript opts then return $ "~" <> contents <> "~" @@ -1167,7 +1164,7 @@ inlineToMarkdown opts (Code attr str) = do then 0 else maximum $ map T.length tickGroups let marker = T.replicate (longest + 1) "`" - let spacer = if (longest == 0) then "" else " " + let spacer = if longest == 0 then "" else " " let attrs = if isEnabled Ext_inline_code_attributes opts && attr /= nullAttr then attrsToMarkdown attr else empty @@ -1296,7 +1293,7 @@ inlineToMarkdown opts lnk@(Link attr txt (src, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts) && attr /= nullAttr = -- use raw HTML - (literal . T.strip) <$> + literal . T.strip <$> writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [Plain [lnk]]) | otherwise = do variant <- asks envVariant @@ -1337,7 +1334,7 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts) && attr /= nullAttr = -- use raw HTML - (literal . T.strip) <$> + literal . T.strip <$> writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [Plain [img]]) | otherwise = do variant <- asks envVariant @@ -1352,7 +1349,7 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit)) inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get - let ref = literal $ writerIdentifierPrefix opts <> tshow (stNoteNum st + (length $ stNotes st) - 1) + let ref = literal $ writerIdentifierPrefix opts <> tshow (stNoteNum st + length (stNotes st) - 1) if isEnabled Ext_footnotes opts then return $ "[^" <> ref <> "]" else return $ "[" <> ref <> "]" diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 561053c88..f3aadde59 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -67,9 +67,7 @@ pandocToMs opts (Pandoc meta blocks) = do let authorsMeta = map (escapeStr opts . stringify) $ docAuthors meta hasHighlighting <- gets stHighlighting let highlightingMacros = if hasHighlighting - then case writerHighlightStyle opts of - Nothing -> mempty - Just sty -> styleToMs sty + then maybe mempty styleToMs $ writerHighlightStyle opts else mempty let context = defField "body" main @@ -523,7 +521,7 @@ msFormatter opts _fmtopts = where fmtLine = mconcat . map fmtToken fmtToken (toktype, tok) = - "\\*[" <> (tshow toktype) <> " \"" <> (escapeStr opts tok) <> "\"]" + "\\*[" <> tshow toktype <> " \"" <> escapeStr opts tok <> "\"]" highlightCode :: PandocMonad m => WriterOptions -> Attr -> Text -> MS m (Doc Text) highlightCode opts attr str = diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 36fa7a4c1..e41fb7176 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -71,7 +71,7 @@ pandocToODT opts doc@(Pandoc meta _) = do refArchive <- case writerReferenceDoc opts of Just f -> liftM toArchive $ lift $ P.readFileLazy f - Nothing -> lift $ (toArchive . B.fromStrict) <$> + Nothing -> lift $ toArchive . B.fromStrict <$> P.readDataFile "reference.odt" -- handle formulas and pictures -- picEntriesRef <- P.newIORef ([] :: [Entry]) diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index 3edf2daa3..810a94775 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -40,7 +40,7 @@ writeOPML opts (Pandoc meta blocks) = do writeMarkdown def (Pandoc nullMeta [Plain ils])) meta' let blocks' = makeSections False (Just 1) blocks - main <- (render colwidth . vcat) <$> + main <- render colwidth . vcat <$> mapM (blockToOPML opts) blocks' let context = defField "body" main metadata return $ diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index c6b66382b..bd20d2db6 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -387,7 +387,7 @@ blockToOpenDocument o bs r <- vcat <$> mapM (deflistItemToOpenDocument o) b setInDefinitionList False return r - preformatted s = (flush . vcat) <$> mapM (inPreformattedTags . escapeStringForXML) (T.lines s) + preformatted s = flush . vcat <$> mapM (inPreformattedTags . escapeStringForXML) (T.lines s) mkBlockQuote b = do increaseIndent i <- paraStyle [("style:parent-style-name","Quotations")] diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 656ef6056..603a84acc 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -303,11 +303,11 @@ makeSpeakerNotesMap (Presentation _ slides) = presentationToArchive :: PandocMonad m => WriterOptions -> Presentation -> m Archive presentationToArchive opts pres = do - distArchive <- (toArchive . BL.fromStrict) <$> + distArchive <- toArchive . BL.fromStrict <$> P.readDefaultDataFile "reference.pptx" refArchive <- case writerReferenceDoc opts of Just f -> toArchive <$> P.readFileLazy f - Nothing -> (toArchive . BL.fromStrict) <$> + Nothing -> toArchive . BL.fromStrict <$> P.readDataFile "reference.pptx" utctime <- P.getCurrentTime @@ -351,10 +351,10 @@ curSlideHasSpeakerNotes = getLayout :: PandocMonad m => Layout -> P m Element getLayout layout = do let layoutpath = case layout of - (MetadataSlide{}) -> "ppt/slideLayouts/slideLayout1.xml" - (TitleSlide _) -> "ppt/slideLayouts/slideLayout3.xml" - (ContentSlide _ _) -> "ppt/slideLayouts/slideLayout2.xml" - (TwoColumnSlide{}) -> "ppt/slideLayouts/slideLayout4.xml" + MetadataSlide{} -> "ppt/slideLayouts/slideLayout1.xml" + TitleSlide{} -> "ppt/slideLayouts/slideLayout3.xml" + ContentSlide{} -> "ppt/slideLayouts/slideLayout2.xml" + TwoColumnSlide{} -> "ppt/slideLayouts/slideLayout4.xml" refArchive <- asks envRefArchive distArchive <- asks envDistArchive parseXml refArchive distArchive layoutpath @@ -547,7 +547,7 @@ registerMedia fp caption = do makeMediaEntry :: PandocMonad m => MediaInfo -> P m Entry makeMediaEntry mInfo = do - epochtime <- (floor . utcTimeToPOSIXSeconds) <$> asks envUTCTime + epochtime <- floor . utcTimeToPOSIXSeconds <$> asks envUTCTime (imgBytes, _) <- P.fetchItem (T.pack $ mInfoFilePath mInfo) let ext = fromMaybe "" (mInfoExt mInfo) let fp = "ppt/media/image" <> @@ -1473,7 +1473,7 @@ presentationToRelsEntry pres = do elemToEntry :: PandocMonad m => FilePath -> Element -> P m Entry elemToEntry fp element = do - epochtime <- (floor . utcTimeToPOSIXSeconds) <$> asks envUTCTime + epochtime <- floor . utcTimeToPOSIXSeconds <$> asks envUTCTime return $ toEntry fp epochtime $ renderXml element slideToEntry :: PandocMonad m => Slide -> P m Entry @@ -1500,8 +1500,7 @@ slideToSpeakerNotesEntry slide = do slideToSpeakerNotesRelElement :: PandocMonad m => Slide -> P m (Maybe Element) slideToSpeakerNotesRelElement (Slide _ _ (SpeakerNotes [])) = return Nothing -slideToSpeakerNotesRelElement slide@( - Slide{}) = do +slideToSpeakerNotesRelElement slide@Slide{} = do idNum <- slideNum slide return $ Just $ mknode "Relationships" @@ -1585,10 +1584,10 @@ slideToSlideRelElement :: PandocMonad m => Slide -> P m Element slideToSlideRelElement slide = do idNum <- slideNum slide let target = case slide of - (Slide _ (MetadataSlide{}) _) -> "../slideLayouts/slideLayout1.xml" - (Slide _ (TitleSlide _) _) -> "../slideLayouts/slideLayout3.xml" - (Slide _ (ContentSlide _ _) _) -> "../slideLayouts/slideLayout2.xml" - (Slide _ (TwoColumnSlide{}) _) -> "../slideLayouts/slideLayout4.xml" + (Slide _ MetadataSlide{} _) -> "../slideLayouts/slideLayout1.xml" + (Slide _ TitleSlide{} _) -> "../slideLayouts/slideLayout3.xml" + (Slide _ ContentSlide{} _) -> "../slideLayouts/slideLayout2.xml" + (Slide _ TwoColumnSlide{} _) -> "../slideLayouts/slideLayout4.xml" speakerNotesRels <- maybeToList <$> speakerNotesSlideRelElement slide @@ -1819,7 +1818,7 @@ getSpeakerNotesFilePaths = do presentationToContentTypes :: PandocMonad m => Presentation -> P m ContentTypes presentationToContentTypes p@(Presentation _ slides) = do - mediaInfos <- (mconcat . M.elems) <$> gets stMediaIds + mediaInfos <- mconcat . M.elems <$> gets stMediaIds filePaths <- patternsToFilePaths $ inheritedPatterns p let mediaFps = filter (match (compile "ppt/media/image*")) filePaths let defaults = [ DefaultContentType "xml" "application/xml" diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index c6d76424d..affec38aa 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -537,10 +537,10 @@ withAttr _ sp = sp blockToShape :: Block -> Pres Shape blockToShape (Plain ils) = blockToShape (Para ils) blockToShape (Para (il:_)) | Image attr ils (url, _) <- il = - (withAttr attr . Pic def (T.unpack url)) <$> inlinesToParElems ils + withAttr attr . Pic def (T.unpack url) <$> inlinesToParElems ils blockToShape (Para (il:_)) | Link _ (il':_) target <- il , Image attr ils (url, _) <- il' = - (withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url)) + withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url) <$> inlinesToParElems ils blockToShape (Table _ blkCapt specs thead tbody tfoot) = do let (caption, algn, _, hdrCells, rows) = toLegacyTable blkCapt specs thead tbody tfoot @@ -721,7 +721,7 @@ makeNoteEntry (n, blks) = let enum = Str (tshow n <> ".") in case blks of - (Para ils : blks') -> (Para $ enum : Space : ils) : blks' + (Para ils : blks') -> Para (enum : Space : ils) : blks' _ -> Para [enum] : blks forceFontSize :: Pixels -> Pres a -> Pres a @@ -767,7 +767,7 @@ getMetaSlide = do mempty addSpeakerNotesToMetaSlide :: Slide -> [Block] -> Pres (Slide, [Block]) -addSpeakerNotesToMetaSlide (Slide sldId layout@(MetadataSlide{}) spkNotes) blks = +addSpeakerNotesToMetaSlide (Slide sldId layout@MetadataSlide{} spkNotes) blks = do let (ntsBlks, blks') = span isNotesDiv blks spkNotes' <- mconcat <$> mapM blockToSpeakerNotes ntsBlks return (Slide sldId layout (spkNotes <> spkNotes'), blks') diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 55c1b470b..e3966ed07 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -241,12 +241,12 @@ blockToRTF _ _ b@(RawBlock f str) | otherwise = do report $ BlockNotRendered b return "" -blockToRTF indent alignment (BulletList lst) = (spaceAtEnd . T.concat) <$> +blockToRTF indent alignment (BulletList lst) = spaceAtEnd . T.concat <$> mapM (listItemToRTF alignment indent (bulletMarker indent)) lst blockToRTF indent alignment (OrderedList attribs lst) = - (spaceAtEnd . T.concat) <$> + spaceAtEnd . T.concat <$> zipWithM (listItemToRTF alignment indent) (orderedMarkers indent attribs) lst -blockToRTF indent alignment (DefinitionList lst) = (spaceAtEnd . T.concat) <$> +blockToRTF indent alignment (DefinitionList lst) = spaceAtEnd . T.concat <$> mapM (definitionListItemToRTF alignment indent) lst blockToRTF indent _ HorizontalRule = return $ rtfPar indent 0 AlignCenter "\\emdash\\emdash\\emdash\\emdash\\emdash" diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index ddf1d76e3..a9ee5eece 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -205,14 +205,14 @@ tableRowToTEI :: PandocMonad m -> [[Block]] -> m (Doc Text) tableRowToTEI opts cols = - (inTagsIndented "row" . vcat) <$> mapM (tableItemToTEI opts) cols + inTagsIndented "row" . vcat <$> mapM (tableItemToTEI opts) cols tableHeadersToTEI :: PandocMonad m => WriterOptions -> [[Block]] -> m (Doc Text) tableHeadersToTEI opts cols = - (inTags True "row" [("role","label")] . vcat) <$> + inTags True "row" [("role","label")] . vcat <$> mapM (tableItemToTEI opts) cols tableItemToTEI :: PandocMonad m @@ -220,7 +220,7 @@ tableItemToTEI :: PandocMonad m -> [Block] -> m (Doc Text) tableItemToTEI opts item = - (inTags False "cell" [] . vcat) <$> mapM (blockToTEI opts) item + inTags False "cell" [] . vcat <$> mapM (blockToTEI opts) item -- | Convert a list of inline elements to TEI. inlinesToTEI :: PandocMonad m => WriterOptions -> [Inline] -> m (Doc Text) diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index cd72d9647..c35235650 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -45,7 +45,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Writers.MediaWiki (highlightingLangs) import Text.Pandoc.Writers.Shared (toLegacyTable) -data WriterState = WriterState { +newtype WriterState = WriterState { listLevel :: Text -- String at the beginning of items } diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index 10ec4f611..4b71d7b69 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ViewPatterns #-} {- | @@ -54,7 +55,7 @@ escapeStringForXML = T.concatMap escapeCharForXML . T.filter isLegalXMLChar -- | Escape newline characters as escapeNls :: Text -> Text -escapeNls = T.concatMap $ \x -> case x of +escapeNls = T.concatMap $ \case '\n' -> " " c -> T.singleton c |