diff options
| author | Albert Krewinkel <[email protected]> | 2024-06-08 22:48:35 +0200 |
|---|---|---|
| committer | Albert Krewinkel <[email protected]> | 2024-06-09 16:10:38 +0200 |
| commit | 2cc9defda43bb4827cc6ab3ee08ca4e44685b7bc (patch) | |
| tree | b216dee6dace7a606f3befd3518beb05c7990273 /pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs | |
| parent | 684668db1ed022a7f26c8e2e8e949a4d08e48549 (diff) | |
Lua: split Init module into more modules.
The module has grown unwieldy and is therefore split into three internal
Haskell modules, `Init`, `Module`, and `Run`.
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs')
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs | 82 |
1 files changed, 82 insertions, 0 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs new file mode 100644 index 000000000..7f89b7f7b --- /dev/null +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs @@ -0,0 +1,82 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{- | + Module : Text.Pandoc.Lua.Run + Copyright : Copyright © 2017-2024 Albert Krewinkel + License : GPL-2.0-or-later + Maintainer : Albert Krewinkel <[email protected]> + +Run code in the Lua interpreter. +-} +module Text.Pandoc.Lua.Run + ( runLua + , runLuaNoEnv + , runLuaWith + ) where + +import Control.Monad.Catch (try) +import Control.Monad.Trans (MonadIO (..)) +import HsLua as Lua hiding (try) +import Text.Pandoc.Class (PandocMonad (..)) +import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Lua.Global (Global (..), setGlobals) +import Text.Pandoc.Lua.Init (initLua) +import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua) + +-- | Run the Lua interpreter, using pandoc's default way of environment +-- initialization. +runLua :: (PandocMonad m, MonadIO m) + => LuaE PandocError a -> m (Either PandocError a) +runLua action = do + runPandocLuaWith Lua.run . try $ do + initLua + liftPandocLua action + +runLuaWith :: (PandocMonad m, MonadIO m) + => GCManagedState -> LuaE PandocError a -> m (Either PandocError a) +runLuaWith luaState action = do + runPandocLuaWith (withGCManagedState luaState) . try $ do + initLua + liftPandocLua action + +-- | Like 'runLua', but ignores all environment variables like @LUA_PATH@. +runLuaNoEnv :: (PandocMonad m, MonadIO m) + => LuaE PandocError a -> m (Either PandocError a) +runLuaNoEnv action = do + runPandocLuaWith Lua.run . try $ do + liftPandocLua $ do + -- This is undocumented, but works -- the code is adapted from the + -- `lua.c` sources for the default interpreter. + Lua.pushboolean True + Lua.setfield Lua.registryindex "LUA_NOENV" + initLua + liftPandocLua action + +-- | Evaluate a @'PandocLua'@ computation, running all contained Lua +-- operations. +runPandocLuaWith :: (PandocMonad m, MonadIO m) + => (forall b. LuaE PandocError b -> IO b) + -> PandocLua a + -> m a +runPandocLuaWith runner pLua = do + origState <- getCommonState + globals <- defaultGlobals + (result, newState) <- liftIO . runner . unPandocLua $ do + putCommonState origState + liftPandocLua $ setGlobals globals + r <- pLua + c <- getCommonState + return (r, c) + putCommonState newState + return result + +-- | Global variables which should always be set. +defaultGlobals :: PandocMonad m => m [Global] +defaultGlobals = do + commonState <- getCommonState + return + [ PANDOC_API_VERSION + , PANDOC_STATE commonState + , PANDOC_VERSION + ] |
