diff --git a/cabal.project b/cabal.project
index 64ab70164..04b79c0a7 100644
--- a/cabal.project
+++ b/cabal.project
@@ -16,7 +16,7 @@ source-repository-package
 source-repository-package
   type: git
   location: https://github.com/jgm/pandoc-types.git
-  tag: 87711e7e60a3981da0f1cc3df9e57f1134f1b82e
+  tag: 99402a46361a3e52805935b1fbe9dfe54f852d6a
 
 source-repository-package
   type: git
diff --git a/pandoc.cabal b/pandoc.cabal
index c13c768f4..615feaccb 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.23     && < 1.24,
+                 pandoc-types          >= 1.22     && < 1.23,
                  parsec                >= 3.1      && < 3.2,
                  process               >= 1.2.3    && < 1.7,
                  random                >= 1        && < 1.3,
@@ -847,7 +847,7 @@ test-suite test-pandoc
                   filepath          >= 1.1     && < 1.5,
                   hslua             >= 1.1     && < 1.4,
                   mtl               >= 2.2     && < 2.3,
-                  pandoc-types      >= 1.23    && < 1.24,
+                  pandoc-types      >= 1.22    && < 1.23,
                   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 a1ad2cda3..8e12d232c 100644
--- a/src/Text/Pandoc/Lua/Marshaling/AST.hs
+++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs
@@ -165,6 +165,7 @@ 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
@@ -188,6 +189,7 @@ 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 6e1f29fb1..06fd052b9 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -920,6 +920,7 @@ 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 f0973178e..bcef4a089 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -140,6 +140,7 @@ 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 0150f7dff..3cafcefba 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -154,6 +154,7 @@ 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 d207f5093..1e9f37d2f 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -116,6 +116,8 @@ 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 3cb68c311..33a6f5f0c 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -165,6 +165,7 @@ 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 a3949792d..686a2f662 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -800,6 +800,7 @@ 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 5fe64717a..602c70ebe 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -98,6 +98,8 @@ 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 f393f031f..6bad37404 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -358,6 +358,7 @@ 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 5992c994f..8fc81ed24 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -730,6 +730,7 @@ 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 9a61c339a..75e14714b 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -90,6 +90,7 @@ 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 8da931406..c254fbc58 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -381,6 +381,7 @@ 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 f20178bd1..9db8723d1 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -251,6 +251,7 @@ 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 709064270..1351814e9 100644
--- a/src/Text/Pandoc/Writers/Jira.hs
+++ b/src/Text/Pandoc/Writers/Jira.hs
@@ -103,6 +103,7 @@ 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 144c3d579..8c45c8db5 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -253,6 +253,7 @@ 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 9514a1ce7..8a34bf47f 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -106,6 +106,7 @@ 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) =
   splitSentences <$> inlineListToMan opts inlines
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 49fb873a9..fda2bbcef 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -313,6 +313,7 @@ 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
@@ -811,7 +812,7 @@ blockListToMarkdown opts blocks = do
       isListBlock (DefinitionList _) = True
       isListBlock _                  = False
       commentSep
-        | variant == PlainText        = RawBlock "html" "<!-- -->\n"
+        | variant == PlainText        = Null
         | 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 899e40418..5029be69f 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -81,6 +81,8 @@ 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 332368a67..eeb8eca62 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -110,6 +110,7 @@ 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 329522a48..d5100f43f 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -275,6 +275,7 @@ 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 27473775b..5f3224c2f 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -398,6 +398,7 @@ 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 aae6fe0ef..f4a22695c 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -102,6 +102,7 @@ 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 99b016a63..fe34d24dc 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -1041,6 +1041,7 @@ 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 88e185897..8b2002851 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -197,6 +197,7 @@ 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 7e3e770ba..063371ebc 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -229,6 +229,7 @@ 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 e8682018b..18015259d 100644
--- a/src/Text/Pandoc/Writers/TEI.hs
+++ b/src/Text/Pandoc/Writers/TEI.hs
@@ -97,6 +97,7 @@ 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 f817900e5..6a33b4283 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -115,6 +115,8 @@ 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 b1a4ed4a0..03d030477 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -100,6 +100,8 @@ 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 0d7387eaa..c35235650 100644
--- a/src/Text/Pandoc/Writers/XWiki.hs
+++ b/src/Text/Pandoc/Writers/XWiki.hs
@@ -74,6 +74,8 @@ 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 651da4e46..df914f590 100644
--- a/src/Text/Pandoc/Writers/ZimWiki.hs
+++ b/src/Text/Pandoc/Writers/ZimWiki.hs
@@ -78,6 +78,8 @@ 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 3d99d80b5..d12ab3587 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -13,9 +13,9 @@ extra-deps:
 - emojis-0.1.2
 - doclayout-0.3.1.1
 - git: https://github.com/jgm/pandoc-types.git
-  commit: 87711e7e60a3981da0f1cc3df9e57f1134f1b82e
+  commit: 99402a46361a3e52805935b1fbe9dfe54f852d6a
 - git: https://github.com/jgm/texmath.git
-  commit: c046e6e5a93510f2c37dbc700f82a2c53ed87b5f
+  commit: 19700530733707284bb41f24add757f19ca23430
 - git: https://github.com/jgm/citeproc.git
   commit: 673a7fb643d24a3bb0f60f8f29e189c0ba7ef15b
 - git: https://github.com/jgm/commonmark-hs.git