diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs
index 790be47d5..79955509d 100644
--- a/src/Text/Pandoc/Lua.hs
+++ b/src/Text/Pandoc/Lua.hs
@@ -37,7 +37,7 @@ import Foreign.Lua (FromLuaStack (peek), Lua, LuaException (..),
 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.Init (runPandocLua, registerScriptPath)
 import Text.Pandoc.Lua.Util (popValue)
 import Text.Pandoc.Options (ReaderOptions)
 import qualified Foreign.Lua as Lua
@@ -55,11 +55,12 @@ runLuaFilter' :: ReaderOptions -> FilePath -> String
 runLuaFilter' ropts filterPath format pd = do
   registerFormat
   registerReaderOptions
+  registerScriptPath filterPath
   top <- Lua.gettop
   stat <- Lua.dofile filterPath
   if stat /= OK
     then do
-      luaErrMsg <- peek (-1) <* Lua.pop 1
+      luaErrMsg <- popValue
       Lua.throwLuaError luaErrMsg
     else do
       newtop <- Lua.gettop
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index d1a26ebad..8fa228837 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -31,6 +31,7 @@ module Text.Pandoc.Lua.Init
   , runPandocLua
   , initLuaState
   , luaPackageParams
+  , registerScriptPath
   ) where
 
 import Control.Monad.Trans (MonadIO (..))
@@ -88,6 +89,11 @@ initLuaState luaPkgParams = do
   loadScriptFromDataDir (luaPkgDataDir luaPkgParams) "init.lua"
   putConstructorsInRegistry
 
+registerScriptPath :: FilePath -> Lua ()
+registerScriptPath fp = do
+  Lua.push fp
+  Lua.setglobal "PANDOC_SCRIPT_FILE"
+
 putConstructorsInRegistry :: Lua ()
 putConstructorsInRegistry = do
   Lua.getglobal "pandoc"
@@ -101,7 +107,7 @@ putConstructorsInRegistry = do
   Lua.pop 1
  where
   constrsToReg :: Data a => a -> Lua ()
-  constrsToReg = mapM_ putInReg . map showConstr . dataTypeConstrs . dataTypeOf
+  constrsToReg = mapM_ (putInReg . showConstr) . dataTypeConstrs . dataTypeOf
 
   putInReg :: String -> Lua ()
   putInReg name = do
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 37b44b646..3daa8d0cf 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -44,7 +44,7 @@ import Foreign.Lua.Api
 import Text.Pandoc.Class (PandocIO)
 import Text.Pandoc.Definition
 import Text.Pandoc.Error
-import Text.Pandoc.Lua.Init (runPandocLua)
+import Text.Pandoc.Lua.Init (runPandocLua, registerScriptPath)
 import Text.Pandoc.Lua.StackInstances ()
 import Text.Pandoc.Lua.Util (addValue, dostring')
 import Text.Pandoc.Options
@@ -106,6 +106,7 @@ writeCustom :: FilePath -> WriterOptions -> Pandoc -> PandocIO Text
 writeCustom luaFile opts doc@(Pandoc meta _) = do
   luaScript <- liftIO $ UTF8.readFile luaFile
   res <- runPandocLua $ do
+    registerScriptPath luaFile
     stat <- dostring' luaScript
     -- check for error in lua script (later we'll change the return type
     -- to handle this more gracefully):
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index b25a6fa4a..b42fda9c8 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -111,6 +111,12 @@ tests = map (localOption (QuickCheckTests 20))
                      , plain (str "to_roman_numeral: OK")
                      ])
 
+  , testCase "Script filename is set" $
+    assertFilterConversion "unexpected script name"
+      "script-name.lua"
+      (doc $ para "ignored")
+      (doc $ para "lua/script-name.lua")
+
   , testCase "Pandoc version is set" . runPandocLua' $ do
       Lua.getglobal' "table.concat"
       Lua.getglobal "PANDOC_VERSION"
diff --git a/test/lua/script-name.lua b/test/lua/script-name.lua
new file mode 100644
index 000000000..4b5a223f0
--- /dev/null
+++ b/test/lua/script-name.lua
@@ -0,0 +1,3 @@
+function Para (_)
+  return pandoc.Para{pandoc.Str(PANDOC_SCRIPT_FILE)}
+end