@@ -27,7 +27,7 @@ import Data.Proxy (Proxy (Proxy))
2727import Data.Text.Encoding.Error (UnicodeException )
2828import HsLua
2929import System.Exit (ExitCode (.. ))
30- import Text.Pandoc.Class ( PandocMonad , FileInfo (.. ), FileTree
30+ import Text.Pandoc.Class ( PandocMonad ( putCommonState ) , FileInfo (.. ), FileTree
3131 , addToFileTree , getCurrentTime
3232 , insertInFileTree , sandboxWithFileTree
3333 )
@@ -36,6 +36,7 @@ import Text.Pandoc.Error (PandocError (..))
3636import Text.Pandoc.Format (FlavoredFormat , parseFlavoredFormat )
3737import Text.Pandoc.Lua.Orphans ()
3838import Text.Pandoc.Lua.Marshal.AST
39+ import Text.Pandoc.Lua.Marshal.CommonState (peekCommonStateFromTable )
3940import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat )
4041import Text.Pandoc.Lua.Marshal.Filter (peekFilter )
4142import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
@@ -222,7 +223,28 @@ stringConstants =
222223
223224functions :: [DocumentedFunction PandocError ]
224225functions =
225- [ defun " pipe"
226+ [ defun " init"
227+ ### (\ newCommonState -> do
228+ getfield registryindex " PANDOC_STATE" >>= \ case
229+ TypeNil -> True <$ unPandocLua (putCommonState newCommonState)
230+ _ -> pure False )
231+ <#> parameter peekCommonStateFromTable " table" " props"
232+ " pandoc state properties"
233+ =#> boolResult " Whether the initialization succeeded."
234+ #? T. unlines
235+ [ " Initialize the pandoc state. This function should be called at most"
236+ , " once, as further invocations won't have any effect. The state is set"
237+ , " only if it hasn't been initialized yet."
238+ , " "
239+ , " Note that the state is always already initialized in filters and in"
240+ , " custom readers or writers. The function is most useful in standalone"
241+ , " pandoc Lua programs."
242+ , " "
243+ , " Returns `true` if the initialization succeeded, and `false` if the Lua"
244+ , " state had been initialized before."
245+ ]
246+
247+ , defun " pipe"
226248 ### (\ command args input -> do
227249 (ec, output) <- Lua. liftIO $ pipeProcess Nothing command args input
228250 `catch` (throwM . PandocIOError " pipe" )
0 commit comments