diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index 7c0e83ee8..6ab6d3718 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -1433,6 +1433,34 @@ Lua functions for pandoc scripts.
 This module exposes internal pandoc functions and utility
 functions.
 
+[`hierarchicalize (blocks)`]{#utils-hierarchicalize}
+
+:   Convert list of blocks into an hierarchical list. An
+    hierarchical elements is either a normal block (but no
+    Header), or a `Sec` element. The latter has the following
+    fields:
+
+    -   level: level in the document hierarchy;
+    -   numbering: list of integers of length `level`,
+        specifying the absolute position of the section in the
+        document;
+    -   attr: section attributes (see [Attr](#Attr));
+    -   contents: nested list of hierarchical elements.
+
+    Returns:
+
+    -   List of hierarchical elements
+
+    Usage:
+
+        local blocks = {
+          pandoc.Header(2, pandoc.Str 'first'),
+          pandoc.Header(2, pandoc.Str 'second'),
+        }
+        local elements = pandoc.utils.hierarchicalize(blocks)
+        print(table.concat(elements[1].numbering, '.')) -- 0.1
+        print(table.concat(elements[2].numbering, '.')) -- 0.2
+
 [`normalize_date (date_string)`]{#utils-normalize_date}
 
 :   Parse a date and convert (if possible) to "YYYY-MM-DD"
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 458716a03..35495dae1 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -44,12 +44,24 @@ import qualified Text.Pandoc.Shared as Shared
 pushModule :: Lua NumResults
 pushModule = do
   Lua.newtable
+  addFunction "hierarchicalize" hierarchicalize
   addFunction "normalize_date" normalizeDate
   addFunction "sha1" sha1
   addFunction "stringify" stringify
   addFunction "to_roman_numeral" toRomanNumeral
   return 1
 
+-- | Convert list of Pandoc blocks into (hierarchical) list of Elements.
+hierarchicalize :: [Block] -> Lua [Shared.Element]
+hierarchicalize = return . Shared.hierarchicalize
+
+-- | Parse a date and convert (if possible) to "YYYY-MM-DD" format. We
+-- limit years to the range 1601-9999 (ISO 8601 accepts greater than
+-- or equal to 1583, but MS Word only accepts dates starting 1601).
+-- Returns nil instead of a string if the conversion failed.
+normalizeDate :: String -> Lua (OrNil String)
+normalizeDate = return . OrNil . Shared.normalizeDate
+
 -- | Calculate the hash of the given contents.
 sha1 :: BSL.ByteString
      -> Lua String
@@ -86,10 +98,3 @@ instance FromLuaStack AstElement where
 -- | Convert a number < 4000 to uppercase roman numeral.
 toRomanNumeral :: LuaInteger -> Lua String
 toRomanNumeral = return . Shared.toRomanNumeral . fromIntegral
-
--- | Parse a date and convert (if possible) to "YYYY-MM-DD" format. We
--- limit years to the range 1601-9999 (ISO 8601 accepts greater than
--- or equal to 1583, but MS Word only accepts dates starting 1601).
--- Returns nil instead of a string if the conversion failed.
-normalizeDate :: String -> Lua (OrNil String)
-normalizeDate = return . OrNil . Shared.normalizeDate
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index ce6dbdb98..119946b78 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -33,13 +33,15 @@ StackValue instances for pandoc types.
 module Text.Pandoc.Lua.StackInstances () where
 
 import Control.Applicative ((<|>))
+import Control.Monad (when)
 import Foreign.Lua (FromLuaStack (peek), Lua, LuaInteger, LuaNumber, StackIndex,
                     ToLuaStack (push), Type (..), throwLuaError, tryLua)
 import Text.Pandoc.Definition
 import Text.Pandoc.Lua.Util (adjustIndexBy, getTable, pushViaConstructor)
-import Text.Pandoc.Shared (safeRead)
+import Text.Pandoc.Shared (Element (Blk, Sec), safeRead)
 
 import qualified Foreign.Lua as Lua
+import qualified Text.Pandoc.Lua.Util as LuaUtil
 
 instance ToLuaStack Pandoc where
   push (Pandoc meta blocks) =
@@ -306,3 +308,27 @@ instance ToLuaStack LuaAttr where
 
 instance FromLuaStack LuaAttr where
   peek idx = LuaAttr <$> peek idx
+
+--
+-- Hierarchical elements
+--
+instance ToLuaStack Element where
+  push (Blk blk) = push blk
+  push (Sec lvl num attr label contents) = do
+    Lua.newtable
+    LuaUtil.addValue "level" lvl
+    LuaUtil.addValue "numbering" num
+    LuaUtil.addValue "attr" (LuaAttr attr)
+    LuaUtil.addValue "label" label
+    LuaUtil.addValue "contents" contents
+    pushSecMetaTable
+    Lua.setmetatable (-2)
+      where
+        pushSecMetaTable :: Lua ()
+        pushSecMetaTable = do
+          inexistant <- Lua.newmetatable "PandocElementSec"
+          when inexistant $ do
+            LuaUtil.addValue "t" "Sec"
+            Lua.push "__index"
+            Lua.pushvalue (-2)
+            Lua.rawset (-3)
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 7fb4309de..6f495a3ca 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -96,7 +96,8 @@ tests = map (localOption (QuickCheckTests 20))
     assertFilterConversion "pandoc.utils doesn't work as expected."
       "test-pandoc-utils.lua"
       (doc $ para "doesn't matter")
-      (doc $ mconcat [ plain (str "normalize_date: OK")
+      (doc $ mconcat [ plain (str "hierarchicalize: OK")
+                     , plain (str "normalize_date: OK")
                      , plain (str "pipe: OK")
                      , plain (str "failing pipe: OK")
                      , plain (str "read: OK")
diff --git a/test/lua/test-pandoc-utils.lua b/test/lua/test-pandoc-utils.lua
index b79f033f8..c732d2f85 100644
--- a/test/lua/test-pandoc-utils.lua
+++ b/test/lua/test-pandoc-utils.lua
@@ -1,5 +1,20 @@
 utils = require 'pandoc.utils'
 
+-- hierarchicalize
+------------------------------------------------------------------------
+function test_hierarchicalize ()
+  local blks = {
+    pandoc.Header(1, {pandoc.Str 'First'}),
+    pandoc.Header(2, {pandoc.Str 'Second'}),
+    pandoc.Header(2, {pandoc.Str 'Third'}),
+  }
+  local hblks = utils.hierarchicalize(blks)
+  return hblks[1].t == "Sec"
+    and hblks[1].contents[1].t == "Sec"
+    and hblks[1].contents[2].numbering[1] == 1
+    and hblks[1].contents[2].numbering[2] == 2
+end
+
 -- SHA1
 ------------------------------------------------------------------------
 function test_sha1 ()
@@ -87,6 +102,7 @@ end
 
 function Para (el)
   return {
+    pandoc.Plain{pandoc.Str("hierarchicalize: " .. run(test_hierarchicalize))},
     pandoc.Plain{pandoc.Str("normalize_date: " .. run(test_normalize_date))},
     pandoc.Plain{pandoc.Str("pipe: " .. run(test_pipe))},
     pandoc.Plain{pandoc.Str("failing pipe: " .. run(test_failing_pipe))},