aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/AST.hs2
-rw-r--r--src/Text/Pandoc/Shared.hs1
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs1
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs1
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs1
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs1
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs2
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs1
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs1
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs1
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs1
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs1
-rw-r--r--src/Text/Pandoc/Writers/Jira.hs1
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs1
-rw-r--r--src/Text/Pandoc/Writers/Man.hs1
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs3
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs2
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs1
-rw-r--r--src/Text/Pandoc/Writers/Muse.hs1
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs1
-rw-r--r--src/Text/Pandoc/Writers/Org.hs1
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs1
-rw-r--r--src/Text/Pandoc/Writers/RST.hs1
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs1
-rw-r--r--src/Text/Pandoc/Writers/TEI.hs1
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs2
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs2
-rw-r--r--src/Text/Pandoc/Writers/XWiki.hs2
-rw-r--r--src/Text/Pandoc/Writers/ZimWiki.hs2
-rw-r--r--stack.yaml9
32 files changed, 10 insertions, 43 deletions
diff --git a/pandoc.cabal b/pandoc.cabal
index f317c3302..a55dbcc22 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -561,7 +561,7 @@ library
mtl >= 2.2 && < 2.3,
network >= 2.6,
network-uri >= 2.6 && < 2.8,
- pandoc-types >= 1.22 && < 1.23,
+ pandoc-types >= 1.23 && < 1.24,
parsec >= 3.1 && < 3.2,
process >= 1.2.3 && < 1.7,
random >= 1 && < 1.3,
@@ -848,7 +848,7 @@ test-suite test-pandoc
filepath >= 1.1 && < 1.5,
hslua >= 1.1 && < 1.4,
mtl >= 2.2 && < 2.3,
- pandoc-types >= 1.22 && < 1.23,
+ pandoc-types >= 1.23 && < 1.24,
process >= 1.2.3 && < 1.7,
tasty >= 0.11 && < 1.5,
tasty-golden >= 2.3 && < 2.4,
diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs
index 8e12d232c..a1ad2cda3 100644
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs
@@ -165,7 +165,6 @@ pushBlock = \case
LineBlock blcks -> pushViaConstructor "LineBlock" blcks
OrderedList lstAttr list -> pushViaConstructor "OrderedList" list
(LuaListAttributes lstAttr)
- Null -> pushViaConstructor "Null"
Para blcks -> pushViaConstructor "Para" blcks
Plain blcks -> pushViaConstructor "Plain" blcks
RawBlock f cs -> pushViaConstructor "RawBlock" f cs
@@ -189,7 +188,6 @@ peekBlock idx = defineHowTo "get Block value" $! do
"OrderedList" -> (\(LuaListAttributes lstAttr, lst) ->
OrderedList lstAttr lst)
<$!> elementContent
- "Null" -> return Null
"Para" -> Para <$!> elementContent
"Plain" -> Plain <$!> elementContent
"RawBlock" -> uncurry RawBlock <$!> elementContent
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 920edca7b..7bb830d0e 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -948,7 +948,6 @@ blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) =
unTableBody (TableBody _ _ hd bd) = hd <> bd
unTableBodies = concatMap unTableBody
blockToInlines (Div _ blks) = blocksToInlines' blks
-blockToInlines Null = mempty
blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines
blocksToInlinesWithSep sep =
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index bcef4a089..f0973178e 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -140,7 +140,6 @@ blockToAsciiDoc :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> ADW m (Doc Text)
-blockToAsciiDoc _ Null = return empty
blockToAsciiDoc opts (Div (id',"section":_,_)
(Header level (_,cls,kvs) ils : xs)) = do
hdr <- blockToAsciiDoc opts (Header level (id',cls,kvs) ils)
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3cafcefba..0150f7dff 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -154,7 +154,6 @@ toLabel z = T.concatMap go z
-- | Convert Pandoc block element to ConTeXt.
blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text)
-blockToConTeXt Null = return empty
blockToConTeXt (Div attr@(_,"section":_,_)
(Header level _ title' : xs)) = do
header' <- sectionHeader attr level title'
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 1e9f37d2f..d207f5093 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -116,8 +116,6 @@ docToCustom opts (Pandoc (Meta metamap) blocks) = do
blockToCustom :: Block -- ^ Block element
-> Lua String
-blockToCustom Null = return ""
-
blockToCustom (Plain inlines) = Lua.callFunc "Plain" (Stringify inlines)
blockToCustom (Para [Image attr txt (src,tit)]) =
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 33a6f5f0c..3cb68c311 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -165,7 +165,6 @@ imageToDocbook _ attr src = selfClosingTag "imagedata" $
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: PandocMonad m => WriterOptions -> Block -> DB m (Doc Text)
-blockToDocbook _ Null = return empty
-- Add ids to paragraphs in divs with ids - this is needed for
-- pandoc-citeproc to get link anchors in bibliographies:
blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) = do
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 686a2f662..a3949792d 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -800,7 +800,6 @@ blockToOpenXML :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content]
blockToOpenXML opts blk = withDirection $ blockToOpenXML' opts blk
blockToOpenXML' :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content]
-blockToOpenXML' _ Null = return []
blockToOpenXML' opts (Div (ident,_classes,kvs) bs) = do
stylemod <- case lookup dynamicStyleKey kvs of
Just (fromString . T.unpack -> sty) -> do
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 602c70ebe..5fe64717a 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -98,8 +98,6 @@ blockToDokuWiki :: PandocMonad m
-> Block -- ^ Block element
-> DokuWiki m Text
-blockToDokuWiki _ Null = return ""
-
blockToDokuWiki opts (Div _attrs bs) = do
contents <- blockListToDokuWiki opts bs
return $ contents <> "\n"
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 6bad37404..f393f031f 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -358,7 +358,6 @@ blockToXml (Table _ blkCapt specs thead tbody tfoot) = do
align_str AlignCenter = "center"
align_str AlignRight = "right"
align_str AlignDefault = "left"
-blockToXml Null = return []
-- Replace plain text with paragraphs and add line break after paragraphs.
-- It is used to convert plain text from tight list items to paragraphs.
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 8fc81ed24..5992c994f 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -730,7 +730,6 @@ adjustNumbers opts doc =
showSecNum = T.intercalate "." . map tshow
blockToHtmlInner :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html
-blockToHtmlInner _ Null = return mempty
blockToHtmlInner opts (Plain lst) = inlineListToHtml opts lst
blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)])
| "stretch" `elem` classes = do
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 75e14714b..9a61c339a 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -90,7 +90,6 @@ blockToHaddock :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> StateT WriterState m (Doc Text)
-blockToHaddock _ Null = return empty
blockToHaddock opts (Div _ ils) = do
contents <- blockListToHaddock opts ils
return $ contents <> blankline
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index c254fbc58..8da931406 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -381,7 +381,6 @@ blockToICML opts style (Table _ blkCapt specs thead tbody tfoot) =
blockToICML opts style (Div (_ident, _, kvs) lst) =
let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs
in blocksToICML opts (dynamicStyle <> style) lst
-blockToICML _ _ Null = return empty
-- | Convert a list of lists of blocks to ICML list items.
listItemsToICML :: PandocMonad m => WriterOptions -> Text -> Style -> Maybe ListAttributes -> [[Block]] -> WS m (Doc Text)
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 9db8723d1..f20178bd1 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -251,7 +251,6 @@ codeAttr opts (ident,classes,kvs) = (lang, attr)
-- | Convert a Pandoc block element to JATS.
blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m (Doc Text)
-blockToJATS _ Null = return empty
blockToJATS opts (Div (id',"section":_,kvs) (Header _lvl _ ils : xs)) = do
let idAttr = [ ("id", writerIdentifierPrefix opts <> escapeNCName id')
| not (T.null id')]
diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs
index 1351814e9..709064270 100644
--- a/src/Text/Pandoc/Writers/Jira.hs
+++ b/src/Text/Pandoc/Writers/Jira.hs
@@ -103,7 +103,6 @@ toJiraBlocks blocks = do
Para xs -> singleton . Jira.Para <$> toJiraInlines xs
Plain xs -> singleton . Jira.Para <$> toJiraInlines xs
RawBlock fmt cs -> rawBlockToJira fmt cs
- Null -> return mempty
Table _ blkCapt specs thead tbody tfoot -> singleton <$> do
let (_, _, _, hd, body) = toLegacyTable blkCapt specs thead tbody tfoot
headerRow <- if all null hd
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 8c45c8db5..144c3d579 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -253,7 +253,6 @@ isListBlock _ = False
blockToLaTeX :: PandocMonad m
=> Block -- ^ Block to convert
-> LW m (Doc Text)
-blockToLaTeX Null = return empty
blockToLaTeX (Div attr@(identifier,"block":dclasses,_)
(Header _ _ ils : bs)) = do
let blockname
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 87b2d8d21..45516ea06 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -106,7 +106,6 @@ blockToMan :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> StateT WriterState m (Doc Text)
-blockToMan _ Null = return empty
blockToMan opts (Div _ bs) = blockListToMan opts bs
blockToMan opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index fda2bbcef..49fb873a9 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -313,7 +313,6 @@ blockToMarkdown' :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> MD m (Doc Text)
-blockToMarkdown' _ Null = return empty
blockToMarkdown' opts (Div attrs ils) = do
contents <- blockListToMarkdown opts ils
variant <- asks envVariant
@@ -812,7 +811,7 @@ blockListToMarkdown opts blocks = do
isListBlock (DefinitionList _) = True
isListBlock _ = False
commentSep
- | variant == PlainText = Null
+ | variant == PlainText = RawBlock "html" "<!-- -->\n"
| isEnabled Ext_raw_html opts = RawBlock "html" "<!-- -->\n"
| otherwise = RawBlock "markdown" "&nbsp;\n"
mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks)
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 5029be69f..899e40418 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -81,8 +81,6 @@ blockToMediaWiki :: PandocMonad m
=> Block -- ^ Block element
-> MediaWikiWriter m Text
-blockToMediaWiki Null = return ""
-
blockToMediaWiki (Div attrs bs) = do
contents <- blockListToMediaWiki bs
return $ render Nothing (tagWithAttrs "div" attrs) <> "\n\n" <>
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 97c23f24d..055324448 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -110,7 +110,6 @@ blockToMs :: PandocMonad m
=> WriterOptions -- ^ Options
-> Block -- ^ Block element
-> MS m (Doc Text)
-blockToMs _ Null = return empty
blockToMs opts (Div (ident,cls,kvs) bs) = do
let anchor = if T.null ident
then empty
diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index d5100f43f..329522a48 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -275,7 +275,6 @@ blockToMuse (Table _ blkCapt specs thead tbody tfoot) =
(length aligns :| length widths : map length (headers:rows))
isSimple = onlySimpleTableCells (headers : rows) && all (== 0) widths
blockToMuse (Div _ bs) = flatBlockListToMuse bs
-blockToMuse Null = return empty
-- | Return Muse representation of notes collected so far.
currentNotesToMuse :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 5f3224c2f..27473775b 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -398,7 +398,6 @@ blockToOpenDocument o = \case
b@(RawBlock f s) -> if f == Format "opendocument"
then return $ text $ T.unpack s
else empty <$ report (BlockNotRendered b)
- Null -> return empty
where
defList b = do setInDefinitionList True
r <- vcat <$> mapM (deflistItemToOpenDocument o) b
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index f4a22695c..aae6fe0ef 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -102,7 +102,6 @@ isRawFormat f =
blockToOrg :: PandocMonad m
=> Block -- ^ Block element
-> Org m (Doc Text)
-blockToOrg Null = return empty
blockToOrg (Div attr bs) = divToOrg attr bs
blockToOrg (Plain inlines) = inlineListToOrg inlines
-- title beginning with fig: indicates that the image is a figure
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 327774cd8..e3d31d099 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -1041,7 +1041,6 @@ blockIsBlank
HorizontalRule -> True
Table{} -> False
Div _ bls -> all blockIsBlank bls
- Null -> True
textIsBlank :: T.Text -> Bool
textIsBlank = T.all isSpace
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 8b2002851..88e185897 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -197,7 +197,6 @@ bordered contents c =
blockToRST :: PandocMonad m
=> Block -- ^ Block element
-> RST m (Doc Text)
-blockToRST Null = return empty
blockToRST (Div ("",["title"],[]) _) = return empty
-- this is generated by the rst reader and can safely be
-- omitted when we're generating rst
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 063371ebc..7e3e770ba 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -229,7 +229,6 @@ blockToRTF :: PandocMonad m
-> Alignment -- ^ alignment
-> Block -- ^ block to convert
-> m Text
-blockToRTF _ _ Null = return ""
blockToRTF indent alignment (Div _ bs) =
blocksToRTF indent alignment bs
blockToRTF indent alignment (Plain lst) =
diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs
index 18015259d..e8682018b 100644
--- a/src/Text/Pandoc/Writers/TEI.hs
+++ b/src/Text/Pandoc/Writers/TEI.hs
@@ -97,7 +97,6 @@ imageToTEI opts attr src = return $ selfClosingTag "graphic" $
-- | Convert a Pandoc block element to TEI.
blockToTEI :: PandocMonad m => WriterOptions -> Block -> m (Doc Text)
-blockToTEI _ Null = return empty
blockToTEI opts (Div attr@(_,"section":_,_) (Header lvl _ ils : xs)) =
do
-- TEI doesn't allow sections with no content, so insert some if needed
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 6a33b4283..f817900e5 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -115,8 +115,6 @@ blockToTexinfo :: PandocMonad m
=> Block -- ^ Block to convert
-> TI m (Doc Text)
-blockToTexinfo Null = return empty
-
blockToTexinfo (Div _ bs) = blockListToTexinfo bs
blockToTexinfo (Plain lst) =
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 03d030477..b1a4ed4a0 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -100,8 +100,6 @@ blockToTextile :: PandocMonad m
-> Block -- ^ Block element
-> TW m Text
-blockToTextile _ Null = return ""
-
blockToTextile opts (Div attr bs) = do
let startTag = render Nothing $ tagWithAttrs "div" attr
let endTag = "</div>"
diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs
index c35235650..0d7387eaa 100644
--- a/src/Text/Pandoc/Writers/XWiki.hs
+++ b/src/Text/Pandoc/Writers/XWiki.hs
@@ -74,8 +74,6 @@ blockListToXWiki blocks =
blockToXWiki :: PandocMonad m => Block -> XWikiReader m Text
-blockToXWiki Null = return ""
-
blockToXWiki (Div (id', _, _) blocks) = do
content <- blockListToXWiki blocks
return $ genAnchor id' <> content
diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs
index df914f590..651da4e46 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -78,8 +78,6 @@ escapeText = T.replace "__" "''__''" .
-- | Convert Pandoc block element to ZimWiki.
blockToZimWiki :: PandocMonad m => WriterOptions -> Block -> ZW m Text
-blockToZimWiki _ Null = return ""
-
blockToZimWiki opts (Div _attrs bs) = do
contents <- blockListToZimWiki opts bs
return $ contents <> "\n"
diff --git a/stack.yaml b/stack.yaml
index 40704814b..674bc357f 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -10,10 +10,15 @@ extra-deps:
- skylighting-core-0.12
- skylighting-0.12
- doctemplates-0.10
+- git: https://github.com/jgm/pandoc-types.git
+ commit: f796401eaaab780f83c562e97dbb8c8d4b9974d1
- git: https://github.com/jgm/texmath.git
- commit: 19700530733707284bb41f24add757f19ca23430
+ commit: c046e6e5a93510f2c37dbc700f82a2c53ed87b5f
- git: https://github.com/jgm/citeproc.git
- commit: 4a7b98afabebd7a074489ba500d68ee6aa75d3a8
+ commit: 673a7fb643d24a3bb0f60f8f29e189c0ba7ef15b
+- git: https://github.com/jgm/commonmark-hs.git
+ commit: 3cba9f874db7516f49d221a94171b4af010b5bea
+ subdirs: [commonmark-pandoc]
ghc-options:
"$locals": -fhide-source-paths -Wno-missing-home-modules
resolver: lts-18.10