diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index cbceae2ce..1647df7ea 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -2,6 +2,7 @@
 {-# LANGUAGE OverloadedStrings   #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE ViewPatterns        #-}
+{-# LANGUAGE MultiWayIf          #-}
 {-
 Copyright (C) 2006-2018 John MacFarlane <jgm@berkeley.edu>
 
@@ -678,23 +679,31 @@ blockToHtml opts (LineBlock lns) =
     return $ H.div ! A.class_ "line-block" $ htmlLines
 blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
   html5 <- gets stHtml5
+  slideVariant <- gets stSlideVariant
   let kvs = [(k,v) | (k,v) <- kvs', k /= "width"] ++
             [("style", "width:" ++ w ++ ";")
              | ("width",w) <- kvs', "column" `elem` classes]
   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 <- if "columns" `elem` classes
+  let opts' = if | speakerNotes -> opts{ writerIncremental = False }
+                 | "incremental" `elem` classes -> opts{ writerIncremental = True }
+                 | "nonincremental" `elem` classes -> opts{ writerIncremental = False }
+                 | otherwise -> opts
+      -- we remove "incremental" and "nonincremental" if we're in a
+      -- slide presentaiton format.
+      classes' = case slideVariant of
+        NoSlides -> classes
+        _ -> filter (\k -> k /= "incremental" && k /= "nonincremental") classes
+  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)
-                              else (H.div, classes)
-  slideVariant <- gets stSlideVariant
+  let (divtag, classes'') = if html5 && "section" `elem` classes'
+                            then (H5.section, filter (/= "section") classes')
+                            else (H.div, classes')
   if speakerNotes
      then case slideVariant of
                RevealJsSlides -> addAttrs opts' attr $
@@ -706,7 +715,7 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
                NoSlides       -> addAttrs opts' attr $
                            H.div contents'
                _              -> return mempty
-     else addAttrs opts (ident, classes', kvs) $
+     else addAttrs opts (ident, classes'', kvs) $
               divtag contents'
 blockToHtml opts (RawBlock f str) = do
   ishtml <- isRawHtml f
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index c94d256f5..f61c878e5 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -442,54 +442,75 @@ blockToLaTeX :: PandocMonad m
              => Block     -- ^ Block to convert
              -> LW m Doc
 blockToLaTeX Null = return empty
-blockToLaTeX (Div (identifier,classes,kvs) bs) = do
-  beamer <- gets stBeamer
-  linkAnchor' <- hypertarget True identifier empty
-  -- see #2704 for the motivation for adding \leavevmode:
-  let linkAnchor =
-       case bs of
-            Para _ : _
-              | not (isEmpty linkAnchor')
-              -> "\\leavevmode" <> linkAnchor' <> "%"
-            _ -> linkAnchor'
-  let align dir txt = inCmd "begin" dir $$ txt $$ inCmd "end" dir
-  lang <- toLang $ lookup "lang" kvs
-  let wrapColumns = if "columns" `elem` classes
-                       then \contents ->
-                          inCmd "begin" "columns" <> brackets "T"
-                              $$ contents
-                              $$ inCmd "end" "columns"
-                       else id
-      wrapColumn  = if "column" `elem` classes
-                       then \contents ->
-                          let fromPct xs =
-                                case reverse xs of
-                                     '%':ds -> '0':'.': reverse ds
-                                     _      -> xs
-                              w = maybe "0.48" fromPct (lookup "width" kvs)
-                          in  inCmd "begin" "column" <>
-                              braces (text w <> "\\textwidth")
-                              $$ contents
-                              $$ inCmd "end" "column"
-                       else id
-      wrapDir = case lookup "dir" kvs of
-                  Just "rtl" -> align "RTL"
-                  Just "ltr" -> align "LTR"
-                  _          -> id
-      wrapLang txt = case lang of
-                       Just lng -> let (l, o) = toPolyglossiaEnv lng
-                                       ops = if null o
-                                                then ""
-                                                else brackets $ text o
-                                   in  inCmd "begin" (text l) <> ops
-                                       $$ blankline <> txt <> blankline
-                                       $$ inCmd "end" (text l)
-                       Nothing  -> txt
-      wrapNotes txt = if beamer && "notes" `elem` classes
+blockToLaTeX (Div (identifier,classes,kvs) bs)
+  | "incremental" `elem` classes = do
+      let classes' = filter ("incremental"/=) classes
+      beamer <- gets stBeamer
+      if beamer
+        then do oldIncremental <- gets stIncremental
+                modify $ \s -> s{ stIncremental = True }
+                result <- blockToLaTeX $ Div (identifier,classes',kvs) bs
+                modify $ \s -> s{ stIncremental = oldIncremental }
+                return result
+        else blockToLaTeX $ Div (identifier,classes',kvs) bs
+  | "nonincremental" `elem` classes = do
+      let classes' = filter ("nonincremental"/=) classes
+      beamer <- gets stBeamer
+      if beamer
+        then do oldIncremental <- gets stIncremental
+                modify $ \s -> s{ stIncremental = False }
+                result <- blockToLaTeX $ Div (identifier,classes',kvs) bs
+                modify $ \s -> s{ stIncremental = oldIncremental }
+                return result
+        else blockToLaTeX $ Div (identifier,classes',kvs) bs
+  | otherwise = do
+      beamer <- gets stBeamer
+      linkAnchor' <- hypertarget True identifier empty
+    -- see #2704 for the motivation for adding \leavevmode:
+      let linkAnchor =
+            case bs of
+              Para _ : _
+                | not (isEmpty linkAnchor')
+                  -> "\\leavevmode" <> linkAnchor' <> "%"
+              _ -> linkAnchor'
+      let align dir txt = inCmd "begin" dir $$ txt $$ inCmd "end" dir
+      lang <- toLang $ lookup "lang" kvs
+      let wrapColumns = if "columns" `elem` classes
+                        then \contents ->
+                               inCmd "begin" "columns" <> brackets "T"
+                               $$ contents
+                               $$ inCmd "end" "columns"
+                        else id
+          wrapColumn  = if "column" `elem` classes
+                        then \contents ->
+                               let fromPct xs =
+                                     case reverse xs of
+                                       '%':ds -> '0':'.': reverse ds
+                                       _      -> xs
+                                   w = maybe "0.48" fromPct (lookup "width" kvs)
+                               in  inCmd "begin" "column" <>
+                                   braces (text w <> "\\textwidth")
+                                   $$ contents
+                                   $$ inCmd "end" "column"
+                        else id
+          wrapDir = case lookup "dir" kvs of
+                      Just "rtl" -> align "RTL"
+                      Just "ltr" -> align "LTR"
+                      _          -> id
+          wrapLang txt = case lang of
+                           Just lng -> let (l, o) = toPolyglossiaEnv lng
+                                           ops = if null o
+                                                 then ""
+                                                 else brackets $ text o
+                                       in  inCmd "begin" (text l) <> ops
+                                           $$ blankline <> txt <> blankline
+                                           $$ inCmd "end" (text l)
+                           Nothing  -> txt
+          wrapNotes txt = if beamer && "notes" `elem` classes
                           then "\\note" <> braces txt -- speaker notes
                           else linkAnchor $$ txt
-  (wrapColumns . wrapColumn . wrapDir . wrapLang . wrapNotes)
-    <$> blockListToLaTeX bs
+      (wrapColumns . wrapColumn . wrapDir . wrapLang . wrapNotes)
+        <$> blockListToLaTeX bs
 blockToLaTeX (Plain lst) =
   inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
 -- title beginning with fig: indicates that the image is a figure