diff --git a/data/pandoc.lua b/data/pandoc.lua
index c5e20045c..239ca4a3d 100644
--- a/data/pandoc.lua
+++ b/data/pandoc.lua
@@ -627,6 +627,97 @@ M.Superscript = M.Inline:create_constructor(
 -- Helpers
 -- @section helpers
 
+-- Find a value pair in a list.
+-- @function find
+-- @tparam table list to be searched
+-- @param needle element to search for
+-- @param[opt] key when non-nil, compare on this field of each list element
+local function find (alist, needle, key)
+  local test
+  if key then
+    test = function(x) return x[key] == needle end
+  else
+    test = function(x) return x == needle end
+  end
+  for i, k in ipairs(alist) do
+    if test(k) then
+      return i, k
+    end
+  end
+  return nil
+end
+
+-- Lookup a value in an associative list
+-- @function lookup
+-- @tparam {{key, value},...} alist associative list
+-- @param key key for which the associated value is to be looked up
+local function lookup(alist, key)
+  return (select(2, find(alist, key, 1)) or {})[2]
+end
+
+--- Return an iterator which returns key-value pairs of an associative list.
+-- @function apairs
+-- @tparam {{key, value},...} alist associative list
+local apairs = function (alist)
+  local i = 1
+  local cur
+  function nxt ()
+    cur = rawget(alist, i)
+    if cur then
+      i = i + 1
+      return cur[1], cur[2]
+    end
+    return nil
+  end
+  return nxt, nil, nil
+end
+
+-- AttributeList, a metatable to allow table-like access to attribute lists
+-- represented by associative lists.
+local AttributeList = {
+  __index = function (t, k)
+    if type(k) == "number" then
+      return rawget(t, k)
+    else
+      return lookup(t, k)
+    end
+  end,
+
+  __newindex = function (t, k, v)
+    local idx, cur = find(t, k, 1)
+    if v == nil then
+      table.remove(t, idx)
+    elseif cur then
+      cur[2] = v
+    elseif type(k) == "number" then
+      rawset(t, k, v)
+    else
+      rawset(t, #t + 1, {k, v})
+    end
+  end,
+
+  __pairs = apairs
+}
+
+-- convert a table to an associative list. The order of key-value pairs in the
+-- alist is undefined. The table should either contain no numeric keys or
+-- already be an associative list.
+-- @tparam table associative list or table without numeric keys.
+-- @treturn table associative list
+local to_alist = function (tbl)
+  if #tbl ~= 0 or next(tbl) == nil then
+    -- probably already an alist
+    return tbl
+  end
+  local alist = {}
+  local i = 1
+  for k, v in pairs(tbl) do
+    alist[i] = {k, v}
+    i = i + 1
+  end
+  return alist
+end
+
 -- Attr
 M.Attr = {}
 M.Attr._field_names = {identifier = 1, classes = 2, attributes = 3}
@@ -639,7 +730,7 @@ M.Attr._field_names = {identifier = 1, classes = 2, attributes = 3}
 M.Attr.__call = function(t, identifier, classes, attributes)
   identifier = identifier or ''
   classes = classes or {}
-  attributes = attributes or {}
+  attributes = setmetatable(to_alist(attributes or {}), AttributeList)
   local attr = {identifier, classes, attributes}
   setmetatable(attr, t)
   return attr
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index e380be6bb..8caab694c 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -7,9 +7,9 @@ import Test.Tasty (TestTree, localOption)
 import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
 import Test.Tasty.QuickCheck (QuickCheckTests (..), ioProperty, testProperty)
 import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Builder (bulletList, doc, doubleQuoted, emph, header,
-                            linebreak, para, plain, rawBlock, singleQuoted,
-                            space, str, strong, (<>))
+import Text.Pandoc.Builder (bulletList, divWith, doc, doubleQuoted, emph,
+                            header, linebreak, para, plain, rawBlock,
+                            singleQuoted, space, str, strong, (<>))
 import Text.Pandoc.Class (runIOorExplode)
 import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc)
 import Text.Pandoc.Lua
@@ -83,6 +83,14 @@ tests = map (localOption (QuickCheckTests 20))
       "uppercase-header.lua"
       (doc $ header 1 "les états-unis" <> para "text")
       (doc $ header 1 "LES ÉTATS-UNIS" <> para "text")
+
+  , testCase "Attribute lists are convenient to use" $
+    let kv_before = [("one", "1"), ("two", "2"), ("three", "3")]
+        kv_after  = [("one", "eins"), ("three", "3"), ("five", "5")]
+    in assertFilterConversion "Attr doesn't behave as expected"
+      "attr-test.lua"
+      (doc $ divWith ("", [], kv_before) (para "nil"))
+      (doc $ divWith ("", [], kv_after) (para "nil"))
   ]
 
 assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion
diff --git a/test/lua/attr-test.lua b/test/lua/attr-test.lua
new file mode 100644
index 000000000..68dc0012d
--- /dev/null
+++ b/test/lua/attr-test.lua
@@ -0,0 +1,6 @@
+function Div (div)
+  div.attributes.five = ("%d"):format(div.attributes.two + div.attributes.three)
+  div.attributes.two = nil
+  div.attributes.one = "eins"
+  return div
+end