aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'pandoc-lua-engine/src/Text')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs56
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs38
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs24
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs10
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs16
6 files changed, 72 insertions, 74 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs
index 079181d74..d9902df98 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Global.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua
@@ -16,14 +17,18 @@ module Text.Pandoc.Lua.Global
import HsLua as Lua
import HsLua.Module.Version (pushVersion)
-import Text.Pandoc.Class (CommonState)
+import Text.Pandoc.Class ( getInputFiles, getOutputFile, getLog
+ , getRequestHeaders, getResourcePath, getSourceURL
+ , getUserDataDir, getTrace, getVerbosity
+ )
import Text.Pandoc.Definition (Pandoc, pandocTypesVersion)
import Text.Pandoc.Error (PandocError)
-import Text.Pandoc.Lua.Marshal.CommonState (pushCommonState)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Lua.Marshal.LogMessage (pushLogMessage)
import Text.Pandoc.Lua.Marshal.Pandoc (pushPandoc)
import Text.Pandoc.Lua.Marshal.ReaderOptions (pushReaderOptionsReadonly)
import Text.Pandoc.Lua.Marshal.WriterOptions (pushWriterOptions)
-import Text.Pandoc.Lua.PandocLua ()
+import Text.Pandoc.Lua.PandocLua (unPandocLua)
import Text.Pandoc.Options (ReaderOptions, WriterOptions)
import Text.Pandoc.Version (pandocVersion)
@@ -37,7 +42,7 @@ data Global =
| PANDOC_READER_OPTIONS ReaderOptions
| PANDOC_WRITER_OPTIONS WriterOptions
| PANDOC_SCRIPT_FILE FilePath
- | PANDOC_STATE CommonState
+ | PANDOC_STATE
| PANDOC_VERSION
-- Cannot derive instance of Data because of CommonState
@@ -66,8 +71,47 @@ setGlobal global = case global of
PANDOC_SCRIPT_FILE filePath -> do
Lua.pushString filePath
Lua.setglobal "PANDOC_SCRIPT_FILE"
- PANDOC_STATE commonState -> do
- pushCommonState commonState
+ PANDOC_STATE -> do
+ -- The common state is an opaque value. We provide a table that
+ -- contains the values accessible through the PandocMonad API. This
+ -- is for backwards compatibility, as the state used to be exposed
+ -- as a read-only object.
+ Lua.newtable
+ Lua.newmetatable "CommonStateInterface"
+ Lua.pushHaskellFunction $ do
+ Lua.forcePeek (peekText (Lua.nthBottom 2)) >>= \case
+ "input_files" -> do
+ pushPandocList pushString =<< unPandocLua getInputFiles
+ return 1
+ "output_file" -> do
+ maybe pushnil pushString =<< unPandocLua getOutputFile
+ return 1
+ "log" -> do
+ pushPandocList pushLogMessage =<< unPandocLua getLog
+ return 1
+ "request_headers" -> do
+ pushPandocList (pushPair pushText pushText)
+ =<< unPandocLua getRequestHeaders
+ return 1
+ "resource_path" -> do
+ pushPandocList pushString =<< unPandocLua getResourcePath
+ return 1
+ "source_url" -> do
+ maybe pushnil pushText =<< unPandocLua getSourceURL
+ return 1
+ "user_data_dir" -> do
+ maybe pushnil pushString =<< unPandocLua getUserDataDir
+ return 1
+ "trace" -> do
+ pushBool =<< unPandocLua getTrace
+ return 1
+ "verbosity" -> do
+ pushString . show =<< unPandocLua getVerbosity
+ return 1
+ _ ->
+ failLua "Unknown key"
+ Lua.setfield (Lua.nth 2) "__index"
+ Lua.setmetatable (Lua.nth 2)
Lua.setglobal "PANDOC_STATE"
PANDOC_VERSION -> do
pushVersion pandocVersion
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
index b0d2b0990..3f705616d 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
@@ -16,41 +16,15 @@ module Text.Pandoc.Lua.Marshal.CommonState
) where
import HsLua
-import Text.Pandoc.Class (CommonState (..))
-import Text.Pandoc.Lua.Marshal.List (pushPandocList)
-import Text.Pandoc.Lua.Marshal.LogMessage (pushLogMessage)
+import Text.Pandoc.Class (CommonState)
-- | Lua type used for the @CommonState@ object.
+--
+-- This is an opaque value that is required for the Lua interpreter
+-- to become an instance of "PandocMonad".
+--
typeCommonState :: LuaError e => DocumentedType e CommonState
-typeCommonState = deftype "CommonState" []
- [ readonly "input_files" "input files passed to pandoc"
- (pushPandocList pushString, stInputFiles)
-
- , readonly "output_file" "the file to which pandoc will write"
- (maybe pushnil pushString, stOutputFile)
-
- , readonly "log" "list of log messages"
- (pushPandocList pushLogMessage, stLog)
-
- , readonly "request_headers" "headers to add for HTTP requests"
- (pushPandocList (pushPair pushText pushText), stRequestHeaders)
-
- , readonly "resource_path"
- "path to search for resources like included images"
- (pushPandocList pushString, stResourcePath)
-
- , readonly "source_url" "absolute URL + dir of 1st source file"
- (maybe pushnil pushText, stSourceURL)
-
- , readonly "user_data_dir" "directory to search for data files"
- (maybe pushnil pushString, stUserDataDir)
-
- , readonly "trace" "controls whether tracing messages are issued"
- (pushBool, stTrace)
-
- , readonly "verbosity" "verbosity level"
- (pushString . show, stVerbosity)
- ]
+typeCommonState = deftype "CommonState" [] []
peekCommonState :: LuaError e => Peeker e CommonState
peekCommonState = peekUD typeCommonState
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
index 135591981..b885cae74 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
@@ -14,14 +14,9 @@ module Text.Pandoc.Lua.Module.Log
import Data.Version (makeVersion)
import HsLua
-import Text.Pandoc.Class
- ( CommonState (stVerbosity, stLog)
- , PandocMonad (putCommonState, getCommonState)
- , report )
+import Text.Pandoc.Class (report, runSilently)
import Text.Pandoc.Error (PandocError)
-import Text.Pandoc.Logging
- ( Verbosity (ERROR)
- , LogMessage (ScriptingInfo, ScriptingWarning) )
+import Text.Pandoc.Logging (LogMessage (ScriptingInfo, ScriptingWarning))
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
import Text.Pandoc.Lua.Marshal.LogMessage (pushLogMessage)
import Text.Pandoc.Lua.PandocLua (liftPandocLua, unPandocLua)
@@ -92,23 +87,12 @@ documentedModule = Module
-- results of the function call after that.
silence :: LuaE PandocError NumResults
silence = unPandocLua $ do
- -- get current log messages
- origState <- getCommonState
- let origLog = stLog origState
- let origVerbosity = stVerbosity origState
- putCommonState (origState { stLog = [], stVerbosity = ERROR })
-
-- call function given as the first argument
- liftPandocLua $ do
+ ((), messages) <- runSilently . liftPandocLua $ do
nargs <- (NumArgs . subtract 1 . fromStackIndex) <$> gettop
call @PandocError nargs multret
- -- restore original log messages
- newState <- getCommonState
- let newLog = stLog newState
- putCommonState (newState { stLog = origLog, stVerbosity = origVerbosity })
-
liftPandocLua $ do
- pushPandocList pushLogMessage newLog
+ pushPandocList pushLogMessage messages
insert 1
(NumResults . fromStackIndex) <$> gettop
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
index da666779a..0e21c6340 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -18,8 +18,7 @@ import Data.Version (makeVersion)
import HsLua ( LuaE, DocumentedFunction, Module (..)
, (<#>), (###), (=#>), (=?>), (#?), defun, functionResult
, opt, parameter, since, stringParam, textParam)
-import Text.Pandoc.Class ( CommonState (..), fetchItem, fillMediaBag
- , getMediaBag, modifyCommonState, setMediaBag)
+import Text.Pandoc.Class ( fetchItem, fillMediaBag, getMediaBag, setMediaBag )
import Text.Pandoc.Class.IO (writeMedia)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc, pushPandoc)
@@ -71,8 +70,9 @@ documentedModule = Module
-- | Delete a single item from the media bag.
delete :: DocumentedFunction PandocError
delete = defun "delete"
- ### (\fp -> unPandocLua $ modifyCommonState
- (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) }))
+ ### (\fp -> unPandocLua $ do
+ mb <- getMediaBag
+ setMediaBag $ MB.deleteMedia fp mb)
<#> stringParam "filepath"
("Filename of the item to deleted. The media bag will be " <>
"left unchanged if no entry with the given filename exists.")
@@ -82,7 +82,7 @@ delete = defun "delete"
-- | Delete all items from the media bag.
empty :: DocumentedFunction PandocError
empty = defun "empty"
- ### unPandocLua (modifyCommonState (\st -> st { stMediaBag = mempty }))
+ ### unPandocLua (setMediaBag mempty)
=#> []
#? "Clear-out the media bag, deleting all items."
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs
index 242281b08..a968b30d3 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/PandocLua.hs
@@ -81,9 +81,7 @@ instance PandocMonad PandocLua where
forcePeek $ peekCommonState Lua.top `lastly` pop 1
putCommonState cst = PandocLua $ do
pushCommonState cst
- Lua.pushvalue Lua.top
Lua.setfield registryindex "PANDOC_STATE"
- Lua.setglobal "PANDOC_STATE"
logOutput = IO.logOutput
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs
index f3bc6ebdd..19c2d0241 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Run.hs
@@ -61,7 +61,7 @@ runPandocLuaWith :: (PandocMonad m, MonadIO m)
-> m a
runPandocLuaWith runner pLua = do
origState <- getCommonState
- globals <- defaultGlobals
+ let globals = defaultGlobals
(result, newState) <- liftIO . runner . unPandocLua $ do
putCommonState origState
liftPandocLua $ setGlobals globals
@@ -72,11 +72,9 @@ runPandocLuaWith runner pLua = do
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
- ]
+defaultGlobals :: [Global]
+defaultGlobals =
+ [ PANDOC_API_VERSION
+ , PANDOC_STATE
+ , PANDOC_VERSION
+ ]