diff options
| author | Alexander Krotov <ilabdsf@gmail.com> | 2017-11-01 14:20:03 +0300 |
|---|---|---|
| committer | Alexander Krotov <ilabdsf@gmail.com> | 2017-11-01 14:40:10 +0300 |
| commit | 00b64f337da635e3cb2fb4bd473d606f48653eb5 (patch) | |
| tree | 115cf6552795e9b113a8d4a6f4fb242a1e1b92da /src/Text/Pandoc/Writers | |
| parent | 3cee9c89768de064910deedbce3d8d28c1ffef84 (diff) | |
| download | pandoc-00b64f337da635e3cb2fb4bd473d606f48653eb5.tar.gz | |
hlint
Diffstat (limited to 'src/Text/Pandoc/Writers')
| -rw-r--r-- | src/Text/Pandoc/Writers/FB2.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ICML.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 4 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/TEI.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/ZimWiki.hs | 4 |
9 files changed, 14 insertions, 14 deletions
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 2d7516daf..633f42442 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -329,7 +329,7 @@ blockToXml (LineBlock lns) = blockToXml (OrderedList a bss) = do state <- get let pmrk = parentListMarker state - let markers = map (pmrk ++) $ orderedListMarkers a + let markers = (pmrk ++) <$> orderedListMarkers a let mkitem mrk bs = do modify (\s -> s { parentListMarker = mrk ++ " "}) item <- cMapM blockToXml $ plainToPara $ indentBlocks (mrk ++ " ") bs diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 4afa23cb9..ba274fb59 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -204,9 +204,9 @@ parStylesToDoc st = vcat $ map makeStyle $ Set.toAscList $ blockStyles st where numbering | isOrderedList = [("NumberingExpression", "^#.^t"), ("NumberingLevel", show nOrds)] | otherwise = [] - listType | isOrderedList && not (isInfixOf subListParName s) + listType | isOrderedList && not (subListParName `isInfixOf` s) = [("BulletsAndNumberingListType", "NumberedList")] - | isBulletList && not (isInfixOf subListParName s) + | isBulletList && not (subListParName `isInfixOf` s) = [("BulletsAndNumberingListType", "BulletList")] | otherwise = [] indent = [("LeftIndent", show indt)] @@ -350,7 +350,7 @@ blockToICML opts style (Table caption aligns widths headers rows) = cells <- rowsToICML tabl (0::Int) let colWidths w = [("SingleColumnWidth",show $ 500 * w) | w > 0] - let tupToDoc tup = selfClosingTag "Column" $ ("Name",show $ fst tup) : (colWidths $ snd tup) + let tupToDoc tup = selfClosingTag "Column" $ ("Name",show $ fst tup) : colWidths (snd tup) let colDescs = vcat $ zipWith (curry tupToDoc) [0..nrCols-1] widths let tableDoc = return $ inTags True "Table" [ ("AppliedTableStyle","TableStyle/Table") diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 976450dcd..156af4bb2 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -835,7 +835,7 @@ defListItemToLaTeX (term, defs) = do else term' def' <- liftM vsep $ mapM blockListToLaTeX defs return $ case defs of - ((Header _ _ _ : _) : _) -> + ((Header{} : _) : _) -> "\\item" <> brackets term'' <> " ~ " $$ def' _ -> "\\item" <> brackets term'' $$ def' diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index fcd551227..390d7c3ba 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -116,8 +116,8 @@ pandocToODT opts doc@(Pandoc meta _) = do ,("manifest:version","1.2")] ( selfClosingTag "manifest:file-entry" [("manifest:media-type","application/vnd.oasis.opendocument.text") ,("manifest:full-path","/")] - $$ vcat ( map toFileEntry $ files ) - $$ vcat ( map toFileEntry $ formulas ) + $$ vcat ( map toFileEntry files ) + $$ vcat ( map toFileEntry formulas ) ) ) let archive' = addEntryToArchive manifestEntry archive diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index ac4a85670..702349636 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -572,7 +572,7 @@ paraStyle attrs = do t <- gets stTight let styleAttr = [ ("style:name" , "P" ++ show pn) , ("style:family" , "paragraph" )] - indentVal = flip (++) "in" . show $ if b then (max 0.5 i) else i + indentVal = flip (++) "in" . show $ if b then max 0.5 i else i tight = if t then [ ("fo:margin-top" , "0in" ) , ("fo:margin-bottom" , "0in" )] else [] diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index aab8a3bf0..42d4d0040 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -437,8 +437,8 @@ inlineListToRST lst = isComplex (Strikeout _) = True isComplex (Superscript _) = True isComplex (Subscript _) = True - isComplex (Link{}) = True - isComplex (Image{}) = True + isComplex Link{} = True + isComplex Image{} = True isComplex (Code _ _) = True isComplex (Math _ _) = True isComplex (Cite _ (x:_)) = isComplex x diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 917fef3eb..955b3f7f1 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -326,7 +326,7 @@ tableItemToRTF indent alignment item = do spaceAtEnd :: String -> String spaceAtEnd str = if "\\par}\n" `isSuffixOf` str - then take ((length str) - 6) str ++ "\\sa180\\par}\n" + then take (length str - 6) str ++ "\\sa180\\par}\n" else str -- | Convert list item (list of blocks) to RTF. diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index aa87c55e1..8e9d155fa 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -159,7 +159,7 @@ blockToTEI opts (Div (ident,_,_) [Para lst]) = do let attribs = [("id", ident) | not (null ident)] inTags False "p" attribs <$> inlinesToTEI opts lst blockToTEI opts (Div _ bs) = blocksToTEI opts $ map plainToPara bs -blockToTEI _ h@(Header{}) = do +blockToTEI _ h@Header{} = do -- should not occur after hierarchicalize, except inside lists/blockquotes report $ BlockNotRendered h return empty diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 29849aa51..30317db73 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -142,7 +142,7 @@ blockToZimWiki _ (CodeBlock (_,classes,_) str) = do return $ case classes of [] -> "'''\n" ++ cleanupCode str ++ "\n'''\n" -- turn no lang block into a quote block (x:_) -> "{{{code: lang=\"" ++ - (fromMaybe x (Map.lookup x langmap)) ++ "\" linenumbers=\"True\"\n" ++ str ++ "\n}}}\n" -- for zim's code plugin, go verbatim on the lang spec + fromMaybe x (Map.lookup x langmap) ++ "\" linenumbers=\"True\"\n" ++ str ++ "\n}}}\n" -- for zim's code plugin, go verbatim on the lang spec blockToZimWiki opts (BlockQuote blocks) = do contents <- blockListToZimWiki opts blocks @@ -156,7 +156,7 @@ blockToZimWiki opts (Table capt aligns _ headers rows) = do return $ "" ++ c ++ "\n" headers' <- if all null headers then zipWithM (tableItemToZimWiki opts) aligns (head rows) - else mapM ((inlineListToZimWiki opts) . removeFormatting)headers -- emphasis, links etc. are not allowed in table headers + else mapM (inlineListToZimWiki opts . removeFormatting)headers -- emphasis, links etc. are not allowed in table headers rows' <- mapM (zipWithM (tableItemToZimWiki opts) aligns) rows let widths = map (maximum . map length) $ transpose (headers':rows') let padTo (width, al) s = |
