diff --git a/data/pandoc.lua b/data/pandoc.lua
index d9375af2d..e56df3b6d 100644
--- a/data/pandoc.lua
+++ b/data/pandoc.lua
@@ -23,7 +23,7 @@ THIS SOFTWARE.
 -- @copyright © 2017 Albert Krewinkel
 -- @license MIT
 local M = {
-  _VERSION = "0.3.0"
+  _VERSION = "0.4.0"
 }
 
 local List = require 'pandoc.List'
@@ -657,7 +657,6 @@ M.Superscript = M.Inline:create_constructor(
 
 ------------------------------------------------------------------------
 -- Helpers
--- @section helpers
 
 local function assoc_key_equals (x)
   return function (y) return y[1] == x end
@@ -671,7 +670,7 @@ local function lookup(alist, key)
   return (List.find_if(alist, assoc_key_equals(key)) or {})[2]
 end
 
---- Return an iterator which returns key-value pairs of an associative list.
+-- Return an iterator which returns key-value pairs of an associative list.
 -- @function apairs
 -- @tparam {{key, value},...} alist associative list
 local apairs = function (alist)
@@ -869,40 +868,6 @@ M.LowerAlpha = "LowerAlpha"
 -- @see OrderedList
 M.UpperAlpha = "UpperAlpha"
 
-
-------------------------------------------------------------------------
--- Helper Functions
--- @section helpers
-
---- Use functions defined in the global namespace to create a pandoc filter.
--- All globally defined functions which have names of pandoc elements are
--- collected into a new table.
--- @return A list of filter functions
--- @usage
--- -- within a file defining a pandoc filter:
--- function Str(text)
---   return pandoc.Str(utf8.upper(text))
--- end
---
--- return {pandoc.global_filter()}
--- -- the above is equivallent to
--- -- return {{Str = Str}}
-function M.global_filter()
-  local res = {}
-  function is_filter_function(k)
-    return M.Inline.constructor[k] or
-      M.Block.constructor[k] or
-      k == "Meta" or k == "Doc" or k == "Pandoc" or
-      k == "Block" or k == "Inline"
-  end
-  for k, v in pairs(_G) do
-    if is_filter_function(k) then
-      res[k] = v
-    end
-  end
-  return res
-end
-
 ------------------------------------------------------------------------
 -- Functions which have moved to different modules
 local utils = require 'pandoc.utils'
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index c99625e67..dfd92a35b 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -1172,18 +1172,6 @@ Lua functions for pandoc scripts.
 
     Returns: strong element
 
-## Helpers
-
-[`apairs (value)`]{#apairs}
-
-:   Return an iterator which returns key-value pairs of an
-    associative list.
-
-    Parameters:
-
-    `value`:
-    :   },\...} alist associative list
-
 [`Attr ([identifier[, classes[, attributes]]])`]{#Attr}
 
 :   Create a new set of attributes (Attr).
@@ -1335,25 +1323,80 @@ Lua functions for pandoc scripts.
 
     See also: [OrderedList](#OrderedList)
 
-## Helper Functions
+## Helper functions
 
-[`global_filter ()`]{#global_filter}
+[`pipe (command, args, input)`]{#pipe}
 
-:   Use functions defined in the global namespace to create a
-    pandoc filter.
+:   Runs command with arguments, passing it some input, and
+    returns the output.
 
-    Returns: A list of filter functions
+    Returns:
+
+    -   Output of command.
+
+    Raises:
+
+    -   A table containing the keys `command`, `error_code`, and
+        `output` is thrown if the command exits with a non-zero
+        error code.
 
     Usage:
 
-        -- within a file defining a pandoc filter:
-        function Str(text)
-          return pandoc.Str(utf8.upper(text))
-        end
+        local output = pandoc.pipe("sed", {"-e","s/a/b/"}, "abc")
 
-        return {pandoc.global_filter()}
-        -- the above is equivallent to
-        -- return {{Str = Str}}
+[`walk_block (element, filter)`]{#walk_block}
+
+:   Apply a filter inside a block element, walking its contents.
+
+    Parameters:
+
+    `element`:
+    :   the block element
+
+    `filter`:
+    :   a lua filter (table of functions) to be applied within
+        the block element
+
+    Returns: the transformed block element
+
+[`walk_inline (element, filter)`]{#walk_inline}
+
+:   Apply a filter inside an inline element, walking its
+    contents.
+
+    Parameters:
+
+    `element`:
+    :   the inline element
+
+    `filter`:
+    :   a lua filter (table of functions) to be applied within
+        the inline element
+
+    Returns: the transformed inline element
+
+[`read (markup[, format])`]{#read}
+
+:   Parse the given string into a Pandoc document.
+
+    Parameters:
+
+    `markup`:
+    :   the markup to be parsed
+
+    `format`:
+    :   format specification, defaults to \"markdown\".
+
+    Returns: pandoc document
+
+    Usage:
+
+        local org_markup = "/emphasis/"  -- Input to be read
+        local document = pandoc.read(org_markup, "org")
+        -- Get the first block of the document
+        local block = document.blocks[1]
+        -- The inline element in that block is an `Emph`
+        assert(block.content[1].t == "Emph")
 
 # Module pandoc.utils
 
diff --git a/pandoc.cabal b/pandoc.cabal
index dea141a8f..988241567 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -622,7 +622,8 @@ test-suite test-pandoc
                   QuickCheck >= 2.4 && < 2.11,
                   containers >= 0.4.2.1 && < 0.6,
                   executable-path >= 0.0 && < 0.1,
-                  zip-archive >= 0.2.3.4 && < 0.4
+                  zip-archive >= 0.2.3.4 && < 0.4,
+                  xml >= 1.3.12 && < 1.4
   if flag(old-locale)
      build-depends: old-locale >= 1 && < 1.1,
                     time >= 1.2 && < 1.5
diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs
index ee259e3fd..d02963418 100644
--- a/src/Text/Pandoc/Lua.hs
+++ b/src/Text/Pandoc/Lua.hs
@@ -29,17 +29,16 @@ module Text.Pandoc.Lua
   ( LuaException (..)
   , runLuaFilter
   , runPandocLua
-  , pushPandocModule
   ) where
 
-import Control.Monad (when, (>=>))
+import Control.Monad ((>=>))
 import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
                     Status (OK), ToLuaStack (push))
 import Text.Pandoc.Class (PandocIO)
 import Text.Pandoc.Definition (Pandoc)
 import Text.Pandoc.Lua.Filter (LuaFilter, walkMWithLuaFilter)
 import Text.Pandoc.Lua.Init (runPandocLua)
-import Text.Pandoc.Lua.Module.Pandoc (pushModule) -- TODO: remove
+import Text.Pandoc.Lua.Util (popValue)
 import qualified Foreign.Lua as Lua
 
 -- | Run the Lua filter in @filterPath@ for a transformation to target
@@ -63,25 +62,16 @@ runLuaFilter' filterPath format pd = do
       Lua.throwLuaError luaErrMsg
     else do
       newtop <- Lua.gettop
-      -- Use the implicitly defined global filter if nothing was returned
-      when (newtop - top < 1) pushGlobalFilter
-      luaFilters <- peek (-1)
+      -- Use the returned filters, or the implicitly defined global filter if
+      -- nothing was returned.
+      luaFilters <- if (newtop - top >= 1)
+                    then peek (-1)
+                    else Lua.getglobal "_G" *> fmap (:[]) popValue
       runAll luaFilters pd
  where
   registerFormat = do
     push format
     Lua.setglobal "FORMAT"
 
-pushGlobalFilter :: Lua ()
-pushGlobalFilter = do
-  Lua.newtable
-  Lua.getglobal' "pandoc.global_filter"
-  Lua.call 0 1
-  Lua.rawseti (-2) 1
-
 runAll :: [LuaFilter] -> Pandoc -> Lua Pandoc
 runAll = foldr ((>=>) . walkMWithLuaFilter) return
-
--- | DEPRECATED: Push the pandoc module to the Lua Stack.
-pushPandocModule :: Maybe FilePath -> Lua Lua.NumResults
-pushPandocModule = pushModule
diff --git a/src/Text/Pandoc/Lua/Filter.hs b/src/Text/Pandoc/Lua/Filter.hs
index 687ab2be5..9e109bb52 100644
--- a/src/Text/Pandoc/Lua/Filter.hs
+++ b/src/Text/Pandoc/Lua/Filter.hs
@@ -164,5 +164,3 @@ singleElement x = do
         Lua.throwLuaError $
           "Error while trying to get a filter's return " ++
           "value from lua stack.\n" ++ err
-
-
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index 1f7664fc0..2958bd734 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -37,6 +37,7 @@ module Text.Pandoc.Lua.Util
   , setRawInt
   , addRawInt
   , raiseError
+  , popValue
   , OrNil (..)
   , PushViaCall
   , pushViaCall
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index 46ebd77bd..39fd1bab5 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -5,27 +5,35 @@ module Tests.Writers.Powerpoint (tests) where
 import Control.Exception (throwIO)
 import Text.Pandoc
 import Text.Pandoc.Builder
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Walk
 import Test.Tasty
 import Test.Tasty.HUnit
+import Test.Tasty.QuickCheck
 import Codec.Archive.Zip
-import Data.List (isPrefixOf, isSuffixOf)
+import Text.XML.Light
+import Data.List (isPrefixOf, isSuffixOf, sort)
+import Data.Maybe (mapMaybe)
+
+getPptxArchive :: WriterOptions -> Pandoc -> IO Archive
+getPptxArchive opts pd = do
+  mbs <- runIO $
+         do setUserDataDir $ Just "../data"
+            writePowerpoint opts pd
+  case mbs of
+       Left e   -> throwIO e
+       Right bs -> return $ toArchive bs
 
 ----- Number of Slides -----------
 
 numberOfSlides :: WriterOptions -> Pandoc -> IO Int
 numberOfSlides opts pd = do
-  mbs <- runIO $
-        do setUserDataDir $ Just "../data"
-           writePowerpoint opts pd
-  case mbs of
-       Left e   -> throwIO e
-       Right bs -> do
-         let archive = toArchive bs
-         return $
-           length $
-           filter (isSuffixOf ".xml") $
-           filter (isPrefixOf "ppt/slides/slide") $
-           filesInArchive archive
+  archive <- getPptxArchive opts pd
+  return $
+    length $
+    filter (isSuffixOf ".xml") $
+    filter (isPrefixOf "ppt/slides/slide") $
+    filesInArchive archive
 
 testNumberOfSlides :: TestName -> Int -> WriterOptions -> Pandoc -> TestTree
 testNumberOfSlides name n opts pd =
@@ -52,12 +60,12 @@ numSlideTests = testGroup "Number of slides in output"
     def
     (doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
   , testNumberOfSlides
-    "With h1 slide (using default slide-level)" 2
-    def
+    "With h1 slide (using slide-level 3)" 2
+    def {writerSlideLevel= Just 3}
     (doc $ header 1 "Header" <> para "foo")
   , testNumberOfSlides
-    "With h2 slide (using default slide-level)" 2
-    def
+    "With h2 slide (using slide-level 3)" 3
+    def {writerSlideLevel= Just 3}
     (doc $ header 1 "Header" <> header 2 "subeader" <> para "foo")
   , testNumberOfSlides
     "With image slide, no header" 3
@@ -94,8 +102,68 @@ numSlideTests = testGroup "Number of slides in output"
     def
     (doc $
      para "first slide" <> horizontalRule <> para "last slide")
+  , testNumberOfSlides
+    "with notes slide" 2
+    def
+    (doc $
+      para $ text "Foo" <> note (para "note text"))
   ]
 
+----- Content Types -----------
+
+
+contentTypesFileExists :: WriterOptions -> Pandoc -> TestTree
+contentTypesFileExists opts pd =
+  testCase "Existence of [Content_Types].xml file" $
+  do archive <- getPptxArchive opts pd
+     assertBool "Missing [Content_Types].xml file" $
+       "[Content_Types].xml" `elem` (filesInArchive archive)
+
+
+
+-- We want an "Override" entry for each xml file under ppt/.
+prop_ContentOverrides :: Pandoc -> IO Bool
+prop_ContentOverrides pd = do
+  -- remove Math to avoid warnings
+  let go :: Inline -> Inline
+      go (Math _ _) = Str "Math"
+      go i = i
+      pd' = walk go pd
+  archive <- getPptxArchive def pd'
+  let xmlFiles = filter ("[Content_Types].xml" /=) $
+                  filter (isSuffixOf ".xml") $
+                  filesInArchive archive
+  contentTypes <- case findEntryByPath "[Content_Types].xml" archive of
+                    Just ent -> return $ fromEntry ent
+                    Nothing  -> throwIO $
+                      PandocSomeError "Missing [Content_Types].xml file"
+  typesElem <- case parseXMLDoc contentTypes of
+                    Just element -> return $ element
+                    Nothing      -> throwIO $
+                      PandocSomeError "[Content_Types].xml cannot be parsed"
+  let ns = findAttr (QName "xmlns" Nothing Nothing) typesElem
+      overrides = findChildren (QName "Override" ns Nothing) typesElem
+      partNames = mapMaybe (findAttr (QName "PartName" Nothing Nothing)) overrides
+      -- files in content_types are absolute
+      absXmlFiles = map (\fp -> case fp of
+                                  ('/':_) -> fp
+                                  _       -> '/': fp
+                        )
+                    xmlFiles
+  return $ sort absXmlFiles == sort partNames
+
+contentOverridesTests :: TestTree
+contentOverridesTests = localOption (QuickCheckTests 20) $
+                       testProperty "Content Overrides for each XML file" $
+                       \x -> ioProperty $ prop_ContentOverrides (x :: Pandoc)
+
+contentTypeTests :: TestTree
+contentTypeTests = testGroup "[Content_Types].xml file"
+  [ contentTypesFileExists def (doc $ para "foo")
+  , contentOverridesTests
+  ]
 
 tests :: [TestTree]
-tests = [numSlideTests]
+tests = [ numSlideTests
+        , contentTypeTests
+        ]
diff --git a/tools/update-lua-docs.lua b/tools/update-lua-docs.lua
index 7c5e86d17..746dce984 100644
--- a/tools/update-lua-docs.lua
+++ b/tools/update-lua-docs.lua
@@ -25,7 +25,9 @@ end
 
 function Header (el)
   if in_module_section then
-    if el.level == 1 then
+    if el.level == 1 or
+       -- special case for Module pandoc
+       (el.level == 2 and el.identifier == 'helper-functions') then
       in_module_section = false
       return el
     else