aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/CSS.hs2
-rw-r--r--src/Text/Pandoc/ImageSize.hs4
-rw-r--r--src/Text/Pandoc/Logging.hs14
-rw-r--r--src/Text/Pandoc/Options.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs36
-rw-r--r--src/Text/Pandoc/Pretty.hs2
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs2
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs10
-rw-r--r--src/Text/Pandoc/Shared.hs6
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs2
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs4
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/RST.hs4
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs2
-rw-r--r--src/Text/Pandoc/Writers/TEI.hs2
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs4
18 files changed, 53 insertions, 53 deletions
diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs
index 41be1ea13..d44b5e1e2 100644
--- a/src/Text/Pandoc/CSS.hs
+++ b/src/Text/Pandoc/CSS.hs
@@ -40,4 +40,4 @@ pickStylesToKVs props styleAttr =
pickStyleAttrProps :: [String] -> String -> Maybe String
pickStyleAttrProps lookupProps styleAttr = do
styles <- eitherToMaybe $ parse styleAttrParser "" styleAttr
- foldOrElse Nothing $ map (flip lookup styles) lookupProps
+ foldOrElse Nothing $ map (`lookup` styles) lookupProps
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 5f491e08b..b4206b84b 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -301,8 +301,8 @@ findpHYs x
factor = if u == 1 -- dots per meter
then \z -> z * 254 `div` 10000
else const 72
- in ( factor $ (shift x1 24) + (shift x2 16) + (shift x3 8) + x4,
- factor $ (shift y1 24) + (shift y2 16) + (shift y3 8) + y4 )
+ in ( factor $ shift x1 24 + shift x2 16 + shift x3 8 + x4,
+ factor $ shift y1 24 + shift y2 16 + shift y3 8 + y4 )
| otherwise = findpHYs $ B.drop 1 x -- read another byte
gifSize :: ByteString -> Maybe ImageSize
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index 4723c1119..7f4ae2ada 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -230,7 +230,7 @@ showLogMessage msg =
"Skipped '" ++ s ++ "' at " ++ showPos pos
CouldNotParseYamlMetadata s pos ->
"Could not parse YAML metadata at " ++ showPos pos ++
- if null s then "" else (": " ++ s)
+ if null s then "" else ": " ++ s
DuplicateLinkReference s pos ->
"Duplicate link reference '" ++ s ++ "' at " ++ showPos pos
DuplicateNoteReference s pos ->
@@ -260,20 +260,20 @@ showLogMessage msg =
"Docx parser warning: " ++ s
CouldNotFetchResource fp s ->
"Could not fetch resource '" ++ fp ++ "'" ++
- if null s then "" else (": " ++ s)
+ if null s then "" else ": " ++ s
CouldNotDetermineImageSize fp s ->
"Could not determine image size for '" ++ fp ++ "'" ++
- if null s then "" else (": " ++ s)
+ if null s then "" else ": " ++ s
CouldNotConvertImage fp s ->
"Could not convert image '" ++ fp ++ "'" ++
- if null s then "" else (": " ++ s)
+ if null s then "" else ": " ++ s
CouldNotDetermineMimeType fp ->
"Could not determine mime type for '" ++ fp ++ "'"
CouldNotConvertTeXMath s m ->
"Could not convert TeX math '" ++ s ++ "', rendering as TeX" ++
- if null m then "" else (':':'\n':m)
+ if null m then "" else ':' : '\n' : m
CouldNotParseCSS m ->
- "Could not parse CSS" ++ if null m then "" else (':':'\n':m)
+ "Could not parse CSS" ++ if null m then "" else ':' : '\n' : m
Fetching fp ->
"Fetching " ++ fp ++ "..."
Extracting fp ->
@@ -301,7 +301,7 @@ showLogMessage msg =
"The term " ++ t ++ " has no translation defined."
CouldNotLoadTranslations lang m ->
"Could not load translations for " ++ lang ++
- if null m then "" else ('\n':m)
+ if null m then "" else '\n' : m
messageVerbosity:: LogMessage -> Verbosity
messageVerbosity msg =
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 35c17c2ac..581f4c82a 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -261,4 +261,4 @@ instance Default WriterOptions where
-- | Returns True if the given extension is enabled.
isEnabled :: Extension -> WriterOptions -> Bool
-isEnabled ext opts = ext `extensionEnabled` (writerExtensions opts)
+isEnabled ext opts = ext `extensionEnabled` writerExtensions opts
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index a02034de4..61d3caf3d 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -188,12 +188,12 @@ where
import Control.Monad.Identity
import Control.Monad.Reader
-import Data.Char (chr, isAlphaNum, isAscii, isHexDigit, isPunctuation, isSpace,
+import Data.Char (chr, isAlphaNum, isAscii, isAsciiUpper, isHexDigit, isPunctuation, isSpace,
ord, toLower, toUpper)
import Data.Default
import Data.List (intercalate, isSuffixOf, transpose)
import qualified Data.Map as M
-import Data.Maybe (catMaybes)
+import Data.Maybe (mapMaybe)
import Data.Monoid ((<>))
import qualified Data.Set as Set
import Data.Text (Text)
@@ -354,7 +354,7 @@ oneOfStringsCI = oneOfStrings' ciMatch
-- this optimizes toLower by checking common ASCII case
-- first, before calling the expensive unicode-aware
-- function:
- toLower' c | c >= 'A' && c <= 'Z' = chr (ord c + 32)
+ toLower' c | isAsciiUpper c = chr (ord c + 32)
| isAscii c = c
| otherwise = toLower c
@@ -497,19 +497,19 @@ romanNumeral upperCase = do
lookAhead $ oneOf romanDigits
let [one, five, ten, fifty, hundred, fivehundred, thousand] =
map char romanDigits
- thousands <- many thousand >>= (return . (1000 *) . length)
+ thousands <- ((1000 *) . length) <$> many thousand
ninehundreds <- option 0 $ try $ hundred >> thousand >> return 900
- fivehundreds <- many fivehundred >>= (return . (500 *) . length)
+ fivehundreds <- ((500 *) . length) <$> many fivehundred
fourhundreds <- option 0 $ try $ hundred >> fivehundred >> return 400
- hundreds <- many hundred >>= (return . (100 *) . length)
+ hundreds <- ((100 *) . length) <$> many hundred
nineties <- option 0 $ try $ ten >> hundred >> return 90
- fifties <- many fifty >>= (return . (50 *) . length)
+ fifties <- ((50 *) . length) <$> many fifty
forties <- option 0 $ try $ ten >> fifty >> return 40
- tens <- many ten >>= (return . (10 *) . length)
+ tens <- ((10 *) . length) <$> many ten
nines <- option 0 $ try $ one >> ten >> return 9
- fives <- many five >>= (return . (5 *) . length)
+ fives <- ((5 *) . length) <$> many five
fours <- option 0 $ try $ one >> five >> return 4
- ones <- many one >>= (return . length)
+ ones <- length <$> many one
let total = thousands + ninehundreds + fivehundreds + fourhundreds +
hundreds + nineties + fifties + forties + tens + nines +
fives + fours + ones
@@ -545,7 +545,7 @@ emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain)
isEmailPunct c = c `elem` "!\"#$%&'*+-/=?^_{|}~;"
-- note: sepBy1 from parsec consumes input when sep
-- succeeds and p fails, so we use this variant here.
- sepby1 p sep = (:) <$> p <*> (many (try $ sep >> p))
+ sepby1 p sep = (:) <$> p <*> many (try $ sep >> p)
uriScheme :: Stream s m Char => ParserT s st m String
@@ -568,7 +568,7 @@ uri = try $ do
let percentEscaped = try $ char '%' >> skipMany1 (satisfy isHexDigit)
let entity = () <$ characterReference
let punct = skipMany1 (char ',')
- <|> () <$ (satisfy (\c -> not (isSpace c) && c /= '<' && c /= '>'))
+ <|> () <$ satisfy (\c -> not (isSpace c) && c /= '<' && c /= '>')
let uriChunk = skipMany1 wordChar
<|> percentEscaped
<|> entity
@@ -837,7 +837,7 @@ blankLineBlockLine = try (char '|' >> blankline)
lineBlockLines :: Monad m => ParserT [Char] st m [String]
lineBlockLines = try $ do
lines' <- many1 (lineBlockLine <|> ((:[]) <$> blankLineBlockLine))
- skipMany $ blankline
+ skipMany blankline
return lines'
-- | Parse a table using 'headerParser', 'rowParser',
@@ -868,10 +868,10 @@ tableWith' headerParser rowParser lineParser footerParser = try $ do
lines' <- sequence <$> rowParser indices `sepEndBy1` lineParser
footerParser
numColumns <- getOption readerColumns
- let widths = if (indices == [])
+ let widths = if null indices
then replicate (length aligns) 0.0
else widthsFromIndices numColumns indices
- return $ (aligns, widths, heads, lines')
+ return (aligns, widths, heads, lines')
-- Calculate relative widths of table columns, based on indices
widthsFromIndices :: Int -- Number of columns on terminal
@@ -1271,7 +1271,7 @@ registerHeader (ident,classes,kvs) header' = do
then do
let id' = uniqueIdent (B.toList header') ids
let id'' = if Ext_ascii_identifiers `extensionEnabled` exts
- then catMaybes $ map toAsciiChar id'
+ then mapMaybe toAsciiChar id'
else id'
updateState $ updateIdentifierList $ Set.insert id'
updateState $ updateIdentifierList $ Set.insert id''
@@ -1417,10 +1417,10 @@ a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)
extractIdClass :: Attr -> Attr
extractIdClass (ident, cls, kvs) = (ident', cls', kvs')
where
- ident' = case (lookup "id" kvs) of
+ ident' = case lookup "id" kvs of
Just v -> v
Nothing -> ident
- cls' = case (lookup "class" kvs) of
+ cls' = case lookup "class" kvs of
Just cl -> words cl
Nothing -> cls
kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index ed6dde149..f95bfa8e0 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -357,7 +357,7 @@ mergeBlocks addSpace (IsBlock w1 lns1) (IsBlock w2 lns2) =
| otherwise -> (lns1, lns2)
pad n s = s ++ replicate (n - realLength s) ' '
sp "" = ""
- sp xs = if addSpace then (' ' : xs) else xs
+ sp xs = if addSpace then ' ' : xs else xs
offsetOf :: D -> Int
offsetOf (Text o _) = o
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index 6b864521f..47f4c4088 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -59,7 +59,7 @@ readCommonMark opts s = return $
-- | Returns True if the given extension is enabled.
enabled :: Extension -> ReaderOptions -> Bool
-enabled ext opts = ext `extensionEnabled` (readerExtensions opts)
+enabled ext opts = ext `extensionEnabled` readerExtensions opts
convertEmojis :: String -> String
convertEmojis (':':xs) =
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 915fa852f..e2be1c5bd 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -141,7 +141,7 @@ type TagParser m = HTMLParser m [Tag Text]
pHtml :: PandocMonad m => TagParser m Blocks
pHtml = try $ do
- (TagOpen "html" attr) <- lookAhead $ pAnyTag
+ (TagOpen "html" attr) <- lookAhead pAnyTag
for_ (lookup "lang" attr) $
updateState . B.setMeta "lang" . B.text . T.unpack
pInTags "html" block
@@ -152,7 +152,7 @@ pBody = pInTags "body" block
pHead :: PandocMonad m => TagParser m Blocks
pHead = pInTags "head" $ pTitle <|> pMetaTag <|> pBaseTag <|> (mempty <$ pAnyTag)
where pTitle = pInTags "title" inline >>= setTitle . trimInlines
- setTitle t = mempty <$ (updateState $ B.setMeta "title" t)
+ setTitle t = mempty <$ updateState (B.setMeta "title" t)
pMetaTag = do
mt <- pSatisfy (matchTagOpen "meta" [])
let name = T.unpack $ fromAttrib "name" mt
@@ -233,7 +233,7 @@ eFootnote :: PandocMonad m => TagParser m ()
eFootnote = try $ do
let notes = ["footnote", "rearnote"]
guardEnabled Ext_epub_html_exts
- (TagOpen tag attr') <- lookAhead $ pAnyTag
+ (TagOpen tag attr') <- lookAhead pAnyTag
let attr = toStringAttr attr'
guard (maybe False (flip elem notes) (lookup "type" attr))
let ident = fromMaybe "" (lookup "id" attr)
@@ -478,7 +478,7 @@ pTable = try $ do
let pTh = option [] $ pInTags "tr" (pCell "th")
pTr = try $ skipMany pBlank >>
pInTags "tr" (pCell "td" <|> pCell "th")
- pTBody = do pOptInTag "tbody" $ many1 pTr
+ pTBody = pOptInTag "tbody" $ many1 pTr
head'' <- pOptInTag "thead" pTh
head' <- map snd <$>
(pOptInTag "tbody" $
@@ -1256,7 +1256,7 @@ renderTags' = renderTagsOptions
renderOptions{ optMinimize = matchTags ["hr", "br", "img",
"meta", "link"]
, optRawTag = matchTags ["script", "style"] }
- where matchTags = \tags -> flip elem tags . T.toLower
+ where matchTags tags = flip elem tags . T.toLower
-- EPUB Specific
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 60c8e1a0c..e0ea8b5e7 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -519,8 +519,8 @@ uniqueIdent title' usedIdents
-- | True if block is a Header block.
isHeaderBlock :: Block -> Bool
-isHeaderBlock (Header{}) = True
-isHeaderBlock _ = False
+isHeaderBlock Header{} = True
+isHeaderBlock _ = False
-- | Shift header levels up or down.
headerShift :: Int -> Pandoc -> Pandoc
@@ -584,7 +584,7 @@ renderTags' = renderTagsOptions
renderOptions{ optMinimize = matchTags ["hr", "br", "img",
"meta", "link"]
, optRawTag = matchTags ["script", "style"] }
- where matchTags = \tags -> flip elem tags . map toLower
+ where matchTags tags = flip elem tags . map toLower
--
-- File handling
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 =