aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Util.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2017-12-02 23:07:29 +0100
committerAlbert Krewinkel <albert@zeitkraut.de>2017-12-02 23:07:29 +0100
commitd5b1c7b767a24bda592ea35902b8e1dc971d6d80 (patch)
tree3c39efd50b1390ad4dd447cd5a4c1ee14ae1184a /src/Text/Pandoc/Lua/Util.hs
parenta7953a60b984474b6937e153c62f51b560e6f994 (diff)
downloadpandoc-d5b1c7b767a24bda592ea35902b8e1dc971d6d80.tar.gz
Lua filters: refactor lua module handling
The integration with Lua's package/module system is improved: A pandoc-specific package searcher is prepended to the searchers in `package.searchers`. The modules `pandoc` and `pandoc.mediabag` can now be loaded via `require`.
Diffstat (limited to 'src/Text/Pandoc/Lua/Util.hs')
-rw-r--r--src/Text/Pandoc/Lua/Util.hs33
1 files changed, 32 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index 7960c0670..5803e62dc 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -38,11 +38,18 @@ module Text.Pandoc.Lua.Util
, PushViaCall
, pushViaCall
, pushViaConstructor
+ , loadScriptFromDataDir
+ , dostring'
) where
+import Control.Monad (when)
+import Data.ByteString.Char8 (unpack)
import Foreign.Lua (FromLuaStack (..), Lua, NumArgs, StackIndex,
ToLuaStack (..), getglobal')
-import Foreign.Lua.Api (call, pop, rawget, rawgeti, rawset, rawseti)
+import Foreign.Lua.Api (Status, call, pop, rawget, rawgeti, rawset, rawseti)
+import Text.Pandoc.Class (readDataFile, runIOorExplode, setUserDataDir)
+
+import qualified Foreign.Lua as Lua
-- | Adjust the stack index, assuming that @n@ new elements have been pushed on
-- the stack.
@@ -107,3 +114,27 @@ pushViaCall fn = pushViaCall' fn (return ()) 0
-- | Call a pandoc element constructor within lua, passing all given arguments.
pushViaConstructor :: PushViaCall a => String -> a
pushViaConstructor pandocFn = pushViaCall ("pandoc." ++ pandocFn)
+
+-- | Load a file from pandoc's data directory.
+loadScriptFromDataDir :: Maybe FilePath -> FilePath -> Lua ()
+loadScriptFromDataDir datadir scriptFile = do
+ script <- fmap unpack . Lua.liftIO . runIOorExplode $
+ setUserDataDir datadir >> readDataFile scriptFile
+ status <- dostring' script
+ when (status /= Lua.OK) .
+ Lua.throwTopMessageAsError' $ \msg ->
+ "Couldn't load '" ++ scriptFile ++ "'.\n" ++ msg
+
+-- | Load a string and immediately perform a full garbage collection. This is
+-- important to keep the program from hanging: If the program contained a call
+-- to @require@, the a new loader function was created which then become
+-- garbage. If that function is collected at an inopportune times, i.e. when the
+-- Lua API is called via a function that doesn't allow calling back into Haskell
+-- (getraw, setraw, …). The function's finalizer, and the full program, hangs
+-- when that happens.
+dostring' :: String -> Lua Status
+dostring' script = do
+ loadRes <- Lua.loadstring script
+ if loadRes == Lua.OK
+ then Lua.pcall 0 1 Nothing <* Lua.gc Lua.GCCOLLECT 0
+ else return loadRes