aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2024-06-07 07:53:57 +0200
committerAlbert Krewinkel <[email protected]>2024-06-07 08:36:24 +0200
commit430d525378bc7b318823fb1d5cba09da13ba9453 (patch)
treec0ba774232132d3be2f575dd24e1ee8abd2cf728 /pandoc-lua-engine/src
parent3d6a4d870ad5def20eefd66c1bf273a70b5cc952 (diff)
Lua: allow passing an environment to `run_lua_filter`.
The default is now to use a *copy* of the global environment when running a filter; this ensures better separation when `run_lua_filter` is used multiple times. A custom environment can be specified via the optional third parameter.
Diffstat (limited to 'pandoc-lua-engine/src')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs40
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs28
2 files changed, 58 insertions, 10 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs
index 549b82768..9996da116 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Filter.hs
@@ -1,18 +1,20 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Filter
Copyright : © 2012-2024 John MacFarlane,
© 2017-2024 Albert Krewinkel
-License : GNU GPL, version 2 or above
-Maintainer : Albert Krewinkel <[email protected]>
-Stability : alpha
+License : GPL-2.0-or-later
+Maintainer : Albert Krewinkel <[email protected]>
Types and functions for running Lua filters.
-}
module Text.Pandoc.Lua.Filter
( runFilterFile
+ , runFilterFile'
) where
import Control.Monad ((>=>), (<$!>))
-import HsLua
+import HsLua as Lua
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshal.AST
@@ -20,10 +22,19 @@ import Text.Pandoc.Lua.Marshal.Filter
import Text.Pandoc.Lua.PandocLua ()
-- | Transform document using the filter defined in the given file.
+-- Runs the filter in the global environment.
runFilterFile :: FilePath -> Pandoc -> LuaE PandocError Pandoc
runFilterFile filterPath doc = do
+ Lua.pushglobaltable
+ runFilterFile' Lua.top filterPath doc <* Lua.pop 1
+
+-- | Like 'runFilterFile', but uses the table at the given index as the
+-- environment in which the filter is run.
+runFilterFile' :: StackIndex -> FilePath -> Pandoc
+ -> LuaE PandocError Pandoc
+runFilterFile' envIdx filterPath doc = do
oldtop <- gettop
- stat <- dofileTrace (Just filterPath)
+ stat <- dofileTrace' envIdx (Just filterPath)
if stat /= OK
then throwErrorAsException
else do
@@ -32,10 +43,25 @@ runFilterFile filterPath doc = do
-- filter if nothing was returned.
luaFilters <- forcePeek $
if newtop - oldtop >= 1
- then peekList peekFilter top
- else (:[]) <$!> (liftLua pushglobaltable *> peekFilter top)
+ then peekList peekFilter top -- get from explicit filter table
+ else (:[]) <$!> peekFilter envIdx -- get the implicit filter in _ENV
settop oldtop
runAll luaFilters doc
+-- | Apply Lua filters to a document
runAll :: [Filter] -> Pandoc -> LuaE PandocError Pandoc
runAll = foldr ((>=>) . applyFully) return
+
+-- | Like 'HsLua.Core.Trace.dofileTrace', but uses a local environment.
+dofileTrace' :: LuaError e
+ => StackIndex -- ^ stack index of the environment table
+ -> Maybe FilePath -- ^ file to load (or @Nothing@ for stdin)
+ -> LuaE e Status
+dofileTrace' envIdx fp = do
+ absEnv <- Lua.absindex envIdx
+ loadfile fp >>= \case
+ OK -> do
+ Lua.pushvalue absEnv
+ Just (Name "_ENV") <- Lua.setupvalue (Lua.nth 2) 1
+ pcallTrace 0 multret
+ s -> pure s
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
index 447fafe31..8fe24fd6c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -29,7 +29,7 @@ import Text.Pandoc.Citeproc (getReferences, processCitations)
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Filter (applyJSONFilter)
-import Text.Pandoc.Lua.Filter (runFilterFile)
+import Text.Pandoc.Lua.Filter (runFilterFile')
import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.Reference
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
@@ -251,13 +251,35 @@ references = defun "references"
-- | Run a filter from a file.
run_lua_filter :: DocumentedFunction PandocError
run_lua_filter = defun "run_lua_filter"
- ### (flip runFilterFile)
+ ### (\doc fp mbenv -> do
+ envIdx <- maybe copyOfGlobalTable pure mbenv
+ runFilterFile' envIdx fp doc)
<#> parameter peekPandoc "Pandoc" "doc" "the Pandoc document to filter"
<#> parameter peekString "string" "filter" "filepath of the filter to run"
+ <#> opt (parameter (typeChecked "table" istable pure) "table" "env"
+ "environment to load and run the filter in")
=#> functionResult pushPandoc "Pandoc" "filtered document"
#? ( "Filter the given doc by passing it through a Lua filter." <>
- "\n\nThe filter will be run in the current Lua process."
+ "\n\nThe filter will be run in the current Lua process." <>
+ "\n"
)
+ `since` makeVersion [3,2,1]
+ where
+ copynext :: LuaError e => StackIndex -> LuaE e StackIndex
+ copynext to =
+ Lua.next (nth 2) >>= \case
+ False -> pure to
+ True -> do
+ pushvalue (nth 2)
+ insert (nth 2)
+ rawset to
+ copynext to
+ copyOfGlobalTable :: LuaError e => LuaE e StackIndex
+ copyOfGlobalTable = do
+ newtable
+ pushglobaltable
+ pushnil
+ (copynext =<< absindex (nth 3)) <* pop 1 -- pop source table
-- | Process the document with a JSON filter.
run_json_filter :: DocumentedFunction PandocError