aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs2
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs50
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs29
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs6
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs55
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs18
-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
13 files changed, 77 insertions, 107 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index bf58a755f..3231e1e30 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -219,7 +219,7 @@ blockToAsciiDoc opts (Table caption aligns widths headers rows) = do
AlignCenter -> "^"
AlignRight -> ">"
AlignDefault -> "") ++
- if wi == 0 then "" else (show wi ++ "%")
+ if wi == 0 then "" else show wi ++ "%"
let headerspec = if all null headers
then empty
else text "options=\"header\","
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index cf96393ca..633f42442 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -64,7 +64,6 @@ data FbRenderState = FbRenderState
{ footnotes :: [ (Int, String, [Content]) ] -- ^ #, ID, text
, imagesToFetch :: [ (String, String) ] -- ^ filename, URL or path
, parentListMarker :: String -- ^ list marker of the parent ordered list
- , parentBulletLevel :: Int -- ^ nesting level of the unordered list
, writerOptions :: WriterOptions
} deriving (Show)
@@ -73,7 +72,7 @@ type FBM m = StateT FbRenderState m
newFB :: FbRenderState
newFB = FbRenderState { footnotes = [], imagesToFetch = []
- , parentListMarker = "", parentBulletLevel = 0
+ , parentListMarker = ""
, writerOptions = def }
data ImageMode = NormalImage | InlineImage deriving (Eq)
@@ -95,9 +94,9 @@ pandocToFB2 :: PandocMonad m
pandocToFB2 opts (Pandoc meta blocks) = do
modify (\s -> s { writerOptions = opts })
desc <- description meta
- fp <- frontpage meta
+ title <- cMapM toXml . docTitle $ meta
secs <- renderSections 1 blocks
- let body = el "body" $ fp ++ secs
+ let body = el "body" $ el "title" (el "p" title) : secs
notes <- renderFootnotes
(imgs,missing) <- fmap imagesToFetch get >>= \s -> lift (fetchImages s)
let body' = replaceImagesWithAlt missing body
@@ -111,17 +110,9 @@ pandocToFB2 opts (Pandoc meta blocks) = do
in [ uattr "xmlns" xmlns
, attr ("xmlns", "l") xlink ]
-frontpage :: PandocMonad m => Meta -> FBM m [Content]
-frontpage meta' = do
- t <- cMapM toXml . docTitle $ meta'
- return
- [ el "title" (el "p" t)
- , el "annotation" (map (el "p" . cMap plain)
- (docAuthors meta' ++ [docDate meta']))
- ]
-
description :: PandocMonad m => Meta -> FBM m Content
description meta' = do
+ let genre = el "genre" "unrecognised"
bt <- booktitle meta'
let as = authors meta'
dd <- docdate meta'
@@ -131,7 +122,7 @@ description meta' = do
_ -> []
where iso639 = takeWhile (/= '-') -- Convert BCP 47 to ISO 639
return $ el "description"
- [ el "title-info" (bt ++ as ++ dd ++ lang)
+ [ el "title-info" (genre : (bt ++ as ++ dd ++ lang))
, el "document-info" [ el "program-used" "pandoc" ] -- FIXME: +version
]
@@ -338,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
@@ -347,32 +338,21 @@ blockToXml (OrderedList a bss) = do
concat <$> zipWithM mkitem markers bss
blockToXml (BulletList bss) = do
state <- get
- let level = parentBulletLevel state
let pmrk = parentListMarker state
- let prefix = replicate (length pmrk) ' '
- let bullets = ["\x2022", "\x25e6", "*", "\x2043", "\x2023"]
- let mrk = prefix ++ bullets !! (level `mod` length bullets)
+ let mrk = pmrk ++ "•"
let mkitem bs = do
- modify (\s -> s { parentBulletLevel = level+1 })
+ modify (\s -> s { parentListMarker = mrk ++ " "})
item <- cMapM blockToXml $ plainToPara $ indentBlocks (mrk ++ " ") bs
- modify (\s -> s { parentBulletLevel = level }) -- restore bullet level
+ modify (\s -> s { parentListMarker = pmrk }) -- old parent marker
return item
cMapM mkitem bss
blockToXml (DefinitionList defs) =
cMapM mkdef defs
where
mkdef (term, bss) = do
- def' <- cMapM (cMapM blockToXml . sep . paraToPlain . map indent) bss
+ items <- cMapM (cMapM blockToXml . plainToPara . indentBlocks (replicate 4 ' ')) bss
t <- wrap "strong" term
- return [ el "p" t, el "p" def' ]
- sep blocks =
- if all needsBreak blocks then
- blocks ++ [Plain [LineBreak]]
- else
- blocks
- needsBreak (Para _) = False
- needsBreak (Plain ins) = LineBreak `notElem` ins
- needsBreak _ = True
+ return (el "p" t : items)
blockToXml h@Header{} = do
-- should not occur after hierarchicalize, except inside lists/blockquotes
report $ BlockNotRendered h
@@ -403,14 +383,6 @@ blockToXml (Table caption aligns _ headers rows) = do
align_str AlignDefault = "left"
blockToXml Null = return []
--- Replace paragraphs with plain text and line break.
--- Necessary to simulate multi-paragraph lists in FB2.
-paraToPlain :: [Block] -> [Block]
-paraToPlain [] = []
-paraToPlain (Para inlines : rest) =
- Plain inlines : Plain [LineBreak] : paraToPlain rest
-paraToPlain (p:rest) = p : paraToPlain rest
-
-- Replace plain text with paragraphs and add line break after paragraphs.
-- It is used to convert plain text from tight list items to paragraphs.
plainToPara :: [Block] -> [Block]
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index ffcde3ce7..1999bdbcf 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -101,6 +101,7 @@ data WriterState = WriterState
, stHtml5 :: Bool -- ^ Use HTML5
, stEPUBVersion :: Maybe EPUBVersion -- ^ EPUB version if for epub
, stSlideVariant :: HTMLSlideVariant
+ , stCodeBlockNum :: Int -- ^ Number of code block
}
defaultWriterState :: WriterState
@@ -108,7 +109,8 @@ defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,
stHighlighting = False, stSecNum = [],
stElement = False, stHtml5 = False,
stEPUBVersion = Nothing,
- stSlideVariant = NoSlides}
+ stSlideVariant = NoSlides,
+ stCodeBlockNum = 0}
-- Helpers to render HTML with the appropriate function.
@@ -438,7 +440,7 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
[] -> []
(x:xs) -> x ++ concatMap inDiv xs
let inNl x = mconcat $ nl opts : intersperse (nl opts) x ++ [nl opts]
- let classes' = ["titleslide" | titleSlide] ++ ["slide" | slide] ++
+ let classes' = ["title-slide" | titleSlide] ++ ["slide" | slide] ++
["section" | (slide || writerSectionDivs opts) &&
not html5 ] ++
["level" ++ show level | slide || writerSectionDivs opts ]
@@ -655,7 +657,7 @@ blockToHtml opts (LineBlock lns) =
return $ H.div ! A.class_ "line-block" $ htmlLines
blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
html5 <- gets stHtml5
- let kvs = kvs' ++
+ let kvs = [(k,v) | (k,v) <- kvs', k /= "width"] ++
if "column" `elem` classes
then let w = fromMaybe "48%" (lookup "width" kvs')
in [("style", "width:" ++ w ++ ";min-width:" ++ w ++
@@ -664,7 +666,12 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
let speakerNotes = "notes" `elem` classes
-- we don't want incremental output inside speaker notes, see #1394
let opts' = if speakerNotes then opts{ writerIncremental = False } else opts
- contents <- blockListToHtml opts' bs
+ contents <- if "columns" `elem` classes
+ then -- we don't use blockListToHtml because it inserts
+ -- a newline between the column divs, which throws
+ -- off widths! see #4028
+ mconcat <$> mapM (blockToHtml opts) bs
+ else blockListToHtml opts' bs
let contents' = nl opts >> contents >> nl opts
let (divtag, classes') = if html5 && "section" `elem` classes
then (H5.section, filter (/= "section") classes)
@@ -698,6 +705,12 @@ blockToHtml _ HorizontalRule = do
html5 <- gets stHtml5
return $ if html5 then H5.hr else H.hr
blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
+ id'' <- if null id'
+ then do
+ modify $ \st -> st{ stCodeBlockNum = stCodeBlockNum st + 1 }
+ codeblocknum <- gets stCodeBlockNum
+ return ("cb" ++ show codeblocknum)
+ else return id'
let tolhs = isEnabled Ext_literate_haskell opts &&
any (\c -> map toLower c == "haskell") classes &&
any (\c -> map toLower c == "literate") classes
@@ -711,7 +724,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
else rawCode
hlCode = if isJust (writerHighlightStyle opts)
then highlight (writerSyntaxMap opts) formatHtmlBlock
- (id',classes',keyvals) adjCode
+ (id'',classes',keyvals) adjCode
else Left ""
case hlCode of
Left msg -> do
@@ -720,7 +733,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
addAttrs opts (id',classes,keyvals)
$ H.pre $ H.code $ toHtml adjCode
Right h -> modify (\st -> st{ stHighlighting = True }) >>
- addAttrs opts (id',[],keyvals) h
+ addAttrs opts (id'',[],keyvals) h
blockToHtml opts (BlockQuote blocks) = do
-- in S5, treat list in blockquote specially
-- if default is incremental, make it nonincremental;
@@ -1100,7 +1113,7 @@ inlineToHtml opts inline = do
let link = H.a ! A.href (toValue $ "#" ++
revealSlash ++
writerIdentifierPrefix opts ++ "fn" ++ ref)
- ! A.class_ "footnoteRef"
+ ! A.class_ "footnote-ref"
! prefixedId opts ("fnref" ++ ref)
$ (if isJust epubVersion
then id
@@ -1120,7 +1133,7 @@ blockListToNote :: PandocMonad m => WriterOptions -> String -> [Block] -> StateT
blockListToNote opts ref blocks =
-- If last block is Para or Plain, include the backlink at the end of
-- that block. Otherwise, insert a new Plain block with the backlink.
- let backlink = [Link ("",["footnoteBack"],[]) [Str "↩"] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])]
+ let backlink = [Link ("",["footnote-back"],[]) [Str "↩"] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])]
blocks' = if null blocks
then []
else let lastBlock = last blocks
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/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 2aac777c6..0ac37efba 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -37,7 +37,6 @@ import Data.Generics (everywhere, mkT)
import Data.List (isSuffixOf, partition)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
-import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (languages, languagesByExtension)
@@ -56,38 +55,14 @@ import qualified Text.XML.Light as Xml
data JATSVersion = JATS1_1
deriving (Eq, Show)
-type DB = ReaderT JATSVersion
-
--- | Convert list of authors to a docbook <author> section
-authorToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m B.Inlines
-authorToJATS opts name' = do
- name <- render Nothing <$> inlinesToJATS opts name'
- let colwidth = if writerWrapText opts == WrapAuto
- then Just $ writerColumns opts
- else Nothing
- return $ B.rawInline "docbook" $ render colwidth $
- if ',' `elem` name
- then -- last name first
- let (lastname, rest) = break (==',') name
- firstname = triml rest in
- inTagsSimple "firstname" (text $ escapeStringForXML firstname) <>
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
- else -- last name last
- let namewords = words name
- lengthname = length namewords
- (firstname, lastname) = case lengthname of
- 0 -> ("","")
- 1 -> ("", name)
- n -> (unwords (take (n-1) namewords), last namewords)
- in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
+type JATS = ReaderT JATSVersion
writeJATS :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeJATS opts d =
runReaderT (docToJATS opts d) JATS1_1
-- | Convert Pandoc document to string in JATS format.
-docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> DB m Text
+docToJATS :: PandocMonad m => WriterOptions -> Pandoc -> JATS m Text
docToJATS opts (Pandoc meta blocks) = do
let isBackBlock (Div ("refs",_,_) _) = True
isBackBlock _ = False
@@ -110,14 +85,12 @@ docToJATS opts (Pandoc meta blocks) = do
TopLevelChapter -> 0
TopLevelSection -> 1
TopLevelDefault -> 1
- auths' <- mapM (authorToJATS opts) $ docAuthors meta
- let meta' = B.setMeta "author" auths' meta
metadata <- metaToJSON opts
(fmap (render' . vcat) .
mapM (elementToJATS opts' startLvl) .
hierarchicalize)
(fmap render' . inlinesToJATS opts')
- meta'
+ meta
main <- (render' . vcat) <$>
mapM (elementToJATS opts' startLvl) elements
back <- (render' . vcat) <$>
@@ -132,7 +105,7 @@ docToJATS opts (Pandoc meta blocks) = do
Just tpl -> renderTemplate' tpl context
-- | Convert an Element to JATS.
-elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc
+elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> JATS m Doc
elementToJATS opts _ (Blk block) = blockToJATS opts block
elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do
let idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')]
@@ -144,7 +117,7 @@ elementToJATS opts lvl (Sec _ _num (id',_,kvs) title elements) = do
inTagsSimple "title" title' $$ vcat contents
-- | Convert a list of Pandoc blocks to JATS.
-blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> DB m Doc
+blocksToJATS :: PandocMonad m => WriterOptions -> [Block] -> JATS m Doc
blocksToJATS opts = fmap vcat . mapM (blockToJATS opts)
-- | Auxiliary function to convert Plain block to Para.
@@ -155,13 +128,13 @@ plainToPara x = x
-- | Convert a list of pairs of terms and definitions into a list of
-- JATS varlistentrys.
deflistItemsToJATS :: PandocMonad m
- => WriterOptions -> [([Inline],[[Block]])] -> DB m Doc
+ => WriterOptions -> [([Inline],[[Block]])] -> JATS m Doc
deflistItemsToJATS opts items =
vcat <$> mapM (uncurry (deflistItemToJATS opts)) items
-- | Convert a term and a list of blocks into a JATS varlistentry.
deflistItemToJATS :: PandocMonad m
- => WriterOptions -> [Inline] -> [[Block]] -> DB m Doc
+ => WriterOptions -> [Inline] -> [[Block]] -> JATS m Doc
deflistItemToJATS opts term defs = do
term' <- inlinesToJATS opts term
def' <- blocksToJATS opts $ concatMap (map plainToPara) defs
@@ -171,7 +144,7 @@ deflistItemToJATS opts term defs = do
-- | Convert a list of lists of blocks to a list of JATS list items.
listItemsToJATS :: PandocMonad m
- => WriterOptions -> Maybe [String] -> [[Block]] -> DB m Doc
+ => WriterOptions -> Maybe [String] -> [[Block]] -> JATS m Doc
listItemsToJATS opts markers items =
case markers of
Nothing -> vcat <$> mapM (listItemToJATS opts Nothing) items
@@ -179,7 +152,7 @@ listItemsToJATS opts markers items =
-- | Convert a list of blocks into a JATS list item.
listItemToJATS :: PandocMonad m
- => WriterOptions -> Maybe String -> [Block] -> DB m Doc
+ => WriterOptions -> Maybe String -> [Block] -> JATS m Doc
listItemToJATS opts mbmarker item = do
contents <- blocksToJATS opts item
return $ inTagsIndented "list-item" $
@@ -187,7 +160,7 @@ listItemToJATS opts mbmarker item = do
$$ contents
-- | Convert a Pandoc block element to JATS.
-blockToJATS :: PandocMonad m => WriterOptions -> Block -> DB m Doc
+blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m Doc
blockToJATS _ Null = return empty
-- Bibliography reference:
blockToJATS opts (Div ('r':'e':'f':'-':_,_,_) [Para lst]) =
@@ -311,7 +284,7 @@ tableRowToJATS :: PandocMonad m
=> WriterOptions
-> Bool
-> [[Block]]
- -> DB m Doc
+ -> JATS m Doc
tableRowToJATS opts isHeader cols =
(inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols
@@ -319,17 +292,17 @@ tableItemToJATS :: PandocMonad m
=> WriterOptions
-> Bool
-> [Block]
- -> DB m Doc
+ -> JATS m Doc
tableItemToJATS opts isHeader item =
(inTags True (if isHeader then "th" else "td") [] . vcat) <$>
mapM (blockToJATS opts) item
-- | Convert a list of inline elements to JATS.
-inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> DB m Doc
+inlinesToJATS :: PandocMonad m => WriterOptions -> [Inline] -> JATS m Doc
inlinesToJATS opts lst = hcat <$> mapM (inlineToJATS opts) lst
-- | Convert an inline element to JATS.
-inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> DB m Doc
+inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> JATS m Doc
inlineToJATS _ (Str str) = return $ text $ escapeStringForXML str
inlineToJATS opts (Emph lst) =
inTagsSimple "italic" <$> inlinesToJATS opts lst
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ab1e90b3b..156af4bb2 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -371,6 +371,10 @@ toSlides bs = do
concat `fmap` mapM (elementToBeamer slideLevel) (hierarchicalize bs')
elementToBeamer :: PandocMonad m => Int -> Element -> LW m [Block]
+elementToBeamer _slideLevel (Blk (Div attr bs)) = do
+ -- make sure we support "blocks" inside divs
+ bs' <- concat `fmap` mapM (elementToBeamer 0) (hierarchicalize bs)
+ return [Div attr bs']
elementToBeamer _slideLevel (Blk b) = return [b]
elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
| lvl > slideLevel = do
@@ -831,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/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 5d812b169..a1f30cb0e 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -397,11 +397,19 @@ blockToMarkdown' :: PandocMonad m
blockToMarkdown' _ Null = return empty
blockToMarkdown' opts (Div attrs ils) = do
contents <- blockListToMarkdown opts ils
- return $ if isEnabled Ext_raw_html opts &&
- isEnabled Ext_markdown_in_html_blocks opts
- then tagWithAttrs "div" attrs <> blankline <>
- contents <> blankline <> "</div>" <> blankline
- else contents <> blankline
+ return $
+ case () of
+ _ | isEnabled Ext_fenced_divs opts &&
+ attrs /= nullAttr ->
+ nowrap (text ":::" <+> attrsToMarkdown attrs) $$
+ chomp contents $$
+ text ":::" <> blankline
+ | isEnabled Ext_native_divs opts ||
+ (isEnabled Ext_raw_html opts &&
+ isEnabled Ext_markdown_in_html_blocks opts) ->
+ tagWithAttrs "div" attrs <> blankline <>
+ contents <> blankline <> "</div>" <> blankline
+ | otherwise -> contents <> blankline
blockToMarkdown' opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
-- escape if para starts with ordered list marker
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 =