diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 0400783e3..284b9ae62 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -604,7 +604,7 @@ splitBlocks' cur acc (Para (il:ils) : blks) | isImage il = do
                      then span isNotesDiv blks
                      else ([], blks)
   case cur of
-    [Header n _ _] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel || slideLevel == 0 ->
                             splitBlocks' []
                             (acc ++ [cur ++ [Para [il]] ++ nts])
                             (if null ils then blks' else Para ils : blks')
@@ -615,14 +615,14 @@ splitBlocks' cur acc (tbl@Table{} : blks) = do
   slideLevel <- asks envSlideLevel
   let (nts, blks') = span isNotesDiv blks
   case cur of
-    [Header n _ _] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel || slideLevel == 0 ->
                             splitBlocks' [] (acc ++ [cur ++ [tbl] ++ nts]) blks'
     _ ->  splitBlocks' [] (acc ++ ([cur | not (null cur)]) ++ [tbl : nts]) blks'
 splitBlocks' cur acc (d@(Div (_, classes, _) _): blks) | "columns" `elem` classes =  do
   slideLevel <- asks envSlideLevel
   let (nts, blks') = span isNotesDiv blks
   case cur of
-    [Header n _ _] | n == slideLevel ->
+    [Header n _ _] | n == slideLevel || slideLevel == 0 ->
                             splitBlocks' [] (acc ++ [cur ++ [d] ++ nts]) blks'
     _ ->  splitBlocks' [] (acc ++ ([cur | not (null cur)]) ++ [d : nts]) blks'
 splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks
@@ -630,25 +630,10 @@ splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks
 splitBlocks :: [Block] -> Pres [[Block]]
 splitBlocks = splitBlocks' [] []
 
-blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide
-blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes
-  | n < lvl = do
-      registerAnchorId ident
-      sldId <- asks envCurSlideId
-      hdr <- inlinesToParElems ils
-      return $ Slide sldId (TitleSlide hdr) spkNotes
-  | n == lvl = do
-      registerAnchorId ident
-      hdr <- inlinesToParElems ils
-      -- Now get the slide without the header, and then add the header
-      -- in.
-      slide <- blocksToSlide' lvl blks spkNotes
-      let layout = case slideLayout slide of
-            ContentSlide _ cont          -> ContentSlide hdr cont
-            TwoColumnSlide _ contL contR -> TwoColumnSlide hdr contL contR
-            layout'                     -> layout'
-      return $ slide{slideLayout = layout}
-blocksToSlide' _ (blk : blks) spkNotes
+-- | Assuming the slide title is already handled, convert these blocks to the
+-- body content for the slide.
+bodyBlocksToSlide :: Int -> [Block] -> SpeakerNotes -> Pres Slide
+bodyBlocksToSlide _ (blk : blks) spkNotes
   | Div (_, classes, _) divBlks <- blk
   , "columns" `elem` classes
   , Div (_, clsL, _) blksL : Div (_, clsR, _) blksR : remaining <- divBlks
@@ -669,7 +654,7 @@ blocksToSlide' _ (blk : blks) spkNotes
         sldId
         (TwoColumnSlide [] shapesL shapesR)
         spkNotes
-blocksToSlide' _ (blk : blks) spkNotes = do
+bodyBlocksToSlide _ (blk : blks) spkNotes = do
       inNoteSlide <- asks envInNoteSlide
       shapes <- if inNoteSlide
                 then forceFontSize noteSize $ blocksToShapes (blk : blks)
@@ -680,7 +665,7 @@ blocksToSlide' _ (blk : blks) spkNotes = do
         sldId
         (ContentSlide [] shapes)
         spkNotes
-blocksToSlide' _ [] spkNotes = do
+bodyBlocksToSlide _ [] spkNotes = do
   sldId <- asks envCurSlideId
   return $
     Slide
@@ -688,6 +673,26 @@ blocksToSlide' _ [] spkNotes = do
     (ContentSlide [] [])
     spkNotes
 
+blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide
+blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes
+  | n < lvl = do
+      registerAnchorId ident
+      sldId <- asks envCurSlideId
+      hdr <- inlinesToParElems ils
+      return $ Slide sldId (TitleSlide hdr) spkNotes
+  | n == lvl || lvl == 0 = do
+      registerAnchorId ident
+      hdr <- inlinesToParElems ils
+      -- Now get the slide without the header, and then add the header
+      -- in.
+      slide <- bodyBlocksToSlide lvl blks spkNotes
+      let layout = case slideLayout slide of
+            ContentSlide _ cont          -> ContentSlide hdr cont
+            TwoColumnSlide _ contL contR -> TwoColumnSlide hdr contL contR
+            layout'                     -> layout'
+      return $ slide{slideLayout = layout}
+blocksToSlide' lvl blks spkNotes = bodyBlocksToSlide lvl blks spkNotes
+
 blockToSpeakerNotes :: Block -> Pres SpeakerNotes
 blockToSpeakerNotes (Div (_, ["notes"], _) blks) =
   local (\env -> env{envInSpeakerNotes=True}) $
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index 344d20238..fd6d01d2d 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -146,4 +146,29 @@ tests = groupPptxTests [ pptxTests "Inline formatting"
                                  [(pack "monofont", toVal $ pack "Consolas")] }
                          "pptx/code.native"
                          "pptx/code-custom.pptx"
+                       , pptxTests ("Using slide level 0, if the first thing on "
+                                    <> "a slide is a h1 it's used as the "
+                                    <> "slide title")
+                         def { writerSlideLevel = Just 0 }
+                         "pptx/slide-level-0-h1-with-image.native"
+                         "pptx/slide-level-0-h1-with-image.pptx"
+                       , pptxTests ("Using slide level 0, if the first thing on "
+                                    <> "a slide is a h2 it's used as the "
+                                    <> "slide title")
+                         def { writerSlideLevel = Just 0 }
+                         "pptx/slide-level-0-h2-with-image.native"
+                         "pptx/slide-level-0-h2-with-image.pptx"
+                       , pptxTests ("Using slide level 0, if the first thing on "
+                                    <> "a slide is a heading it's used as the "
+                                    <> "slide title (works with a table)")
+                         def { writerSlideLevel = Just 0 }
+                         "pptx/slide-level-0-h1-with-table.native"
+                         "pptx/slide-level-0-h1-with-table.pptx"
+                       , pptxTests ("Using slide level 0, if the first thing on "
+                                    <> "a slide is a heading it's used as the "
+                                    <> "slide title (two headings forces a "
+                                    <> "slide break though)")
+                         def { writerSlideLevel = Just 0 }
+                         "pptx/slide-level-0-h1-h2-with-table.native"
+                         "pptx/slide-level-0-h1-h2-with-table.pptx"
                        ]
diff --git a/test/pptx/slide-level-0-h1-h2-with-table.native b/test/pptx/slide-level-0-h1-h2-with-table.native
new file mode 100644
index 000000000..c6e65ecf5
--- /dev/null
+++ b/test/pptx/slide-level-0-h1-h2-with-table.native
@@ -0,0 +1,14 @@
+[Header 1 ("hello",[],[]) [Str "Hello"]
+,Header 2 ("there",[],[]) [Str "There"]
+,Table ("",[],[]) (Caption Nothing
+ [])
+ [(AlignDefault,ColWidth 5.555555555555555e-2)]
+ (TableHead ("",[],[])
+ [])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+  []
+  [Row ("",[],[])
+   [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+    [Plain [Str "1"]]]])]
+ (TableFoot ("",[],[])
+ [])]
diff --git a/test/pptx/slide-level-0-h1-h2-with-table.pptx b/test/pptx/slide-level-0-h1-h2-with-table.pptx
new file mode 100644
index 000000000..197a6833f
Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table.pptx differ
diff --git a/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx
new file mode 100644
index 000000000..5e776e05c
Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx
new file mode 100644
index 000000000..35204de1b
Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx b/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx
new file mode 100644
index 000000000..5c659952e
Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-image.native b/test/pptx/slide-level-0-h1-with-image.native
new file mode 100644
index 000000000..0f5033b54
--- /dev/null
+++ b/test/pptx/slide-level-0-h1-with-image.native
@@ -0,0 +1,2 @@
+[Header 1 ("hello",[],[]) [Str "Hello"]
+,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]]
diff --git a/test/pptx/slide-level-0-h1-with-image.pptx b/test/pptx/slide-level-0-h1-with-image.pptx
new file mode 100644
index 000000000..2f3a53f5c
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx
new file mode 100644
index 000000000..16c61d1be
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx
new file mode 100644
index 000000000..395036069
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-image_templated.pptx b/test/pptx/slide-level-0-h1-with-image_templated.pptx
new file mode 100644
index 000000000..d306375e9
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_templated.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-table.native b/test/pptx/slide-level-0-h1-with-table.native
new file mode 100644
index 000000000..b961e900d
--- /dev/null
+++ b/test/pptx/slide-level-0-h1-with-table.native
@@ -0,0 +1,13 @@
+[Header 1 ("hello",[],[]) [Str "Hello"]
+,Table ("",[],[]) (Caption Nothing
+ [])
+ [(AlignDefault,ColWidth 5.555555555555555e-2)]
+ (TableHead ("",[],[])
+ [])
+ [(TableBody ("",[],[]) (RowHeadColumns 0)
+  []
+  [Row ("",[],[])
+   [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
+    [Plain [Str "1"]]]])]
+ (TableFoot ("",[],[])
+ [])]
diff --git a/test/pptx/slide-level-0-h1-with-table.pptx b/test/pptx/slide-level-0-h1-with-table.pptx
new file mode 100644
index 000000000..44dbbf90c
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx
new file mode 100644
index 000000000..0eb7c0b08
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx
new file mode 100644
index 000000000..197499bc3
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h1-with-table_templated.pptx b/test/pptx/slide-level-0-h1-with-table_templated.pptx
new file mode 100644
index 000000000..87b45dda2
Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_templated.pptx differ
diff --git a/test/pptx/slide-level-0-h2-with-image.native b/test/pptx/slide-level-0-h2-with-image.native
new file mode 100644
index 000000000..5def0cb92
--- /dev/null
+++ b/test/pptx/slide-level-0-h2-with-image.native
@@ -0,0 +1,2 @@
+[Header 2 ("hello",[],[]) [Str "Hello"]
+,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]]
diff --git a/test/pptx/slide-level-0-h2-with-image.pptx b/test/pptx/slide-level-0-h2-with-image.pptx
new file mode 100644
index 000000000..948659d6a
Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image.pptx differ
diff --git a/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx
new file mode 100644
index 000000000..afc096ce6
Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx
new file mode 100644
index 000000000..395036069
Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx differ
diff --git a/test/pptx/slide-level-0-h2-with-image_templated.pptx b/test/pptx/slide-level-0-h2-with-image_templated.pptx
new file mode 100644
index 000000000..d306375e9
Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_templated.pptx differ